Quest 1: Whispers in the Shell

  • Keep top level comments as only solutions, if you want to say something other than a solution put it in a new post. (replies to comments can be whatever)
  • You can send code in code blocks by using three backticks, the code, and then three backticks or use something such as https://topaz.github.io/paste/ if you prefer sending it through a URL

Link to participate: https://everybody.codes/

  • VegOwOtenks@lemmy.world
    link
    fedilink
    arrow-up
    2
    ·
    4 days ago

    I coded this along with my girlfriend who’s learning python, but not motivated to share her solution. The program reads from stdin, because I usually invoke it like so: runhaskell Main.hs < input or runhaskell Main.hs < example. I think this is quite handy because I don’t have to change the source code to check the example input again.

    I struggled with Part 3, where I suddenly forgot I could’ve simply used mod, which I ended up doing anyway. I immediately recognized that Part 3 needs Mutable Arrays if I care to avoid Index hell, which is not what I wanted to with Haskell but oh well.

    {-# OPTIONS_GHC -Wall #-}
    {-# LANGUAGE PatternSynonyms #-}
    module Main (main) where
    
    import qualified Data.Text as Text
    import qualified Data.Text.IO as TextIO
    import Control.Monad ((<$!>), forM_)
    import Data.Text (Text, pattern (:<))
    import qualified Data.List as List
    import qualified Data.Array.MArray as MutableArray
    import Control.Monad.ST (runST, ST)
    import Data.Array.ST (STArray)
    
    commaSepLine :: IO [Text.Text]
    commaSepLine = Text.split (== ',') <$!> TextIO.getLine
    
    readInstruction :: Text -> Int
    readInstruction ('R' :< n) = read . Text.unpack $ n
    readInstruction ('L' :< n) = negate . read . Text.unpack $ n
    readInstruction _ = undefined
    
    myName :: (Foldable t, Ord b, Enum b, Num b) => b -> t b -> b
    myName maxPosition = List.foldl' (\ pos offset -> min (pred maxPosition) . max 0 $ pos + offset) 0
    
    parentName1 :: [Int] -> Int
    parentName1 = List.sum
    
    newSTArray :: [e] -> ST s (STArray s Int e)
    newSTArray xs = MutableArray.newListArray (0, length xs - 1) xs
    
    swap :: (MutableArray.MArray a e m, MutableArray.Ix i) => a i e -> i -> i -> m ()
    swap array i0 i1 = do
      e0 <- MutableArray.readArray array i0
      e1 <- MutableArray.readArray array i1
      MutableArray.writeArray array i0 e1
      MutableArray.writeArray array i1 e0
    
    parentName2 :: [Text] -> [Int] -> Text
    parentName2 nameList instructions = runST $ do
      names <- newSTArray nameList
      arrayLength <- succ . snd <$> MutableArray.getBounds names
      forM_ instructions $ \ offset -> do
        let arrayOffset = offset `mod` arrayLength
        swap names 0 arrayOffset
      MutableArray.readArray names 0
    
    main :: IO ()
    main = do
      names <- commaSepLine
      _ <- TextIO.getLine
      instructions <- fmap readInstruction <$> commaSepLine
    
      let namesLength = length names
      print $ names !! myName namesLength instructions
      print . (names !!) . (`mod` namesLength) $ parentName1 instructions
      print $ parentName2 names instructions