day 5, undo clean mistake (that ended up almost deleting actual code)

This commit is contained in:
Jill 2022-12-05 09:10:27 +03:00
parent c57fa1df31
commit 57c1faf04e
4 changed files with 71 additions and 2 deletions

9
.gitignore vendored
View File

@ -1,3 +1,12 @@
# Ignore all
*
# Unignore all with extensions
!*.*
# Unignore all dirs
!*/
dist
dist-*
cabal-dev

30
5-a.hs Normal file
View File

@ -0,0 +1,30 @@
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text as T
import GHC.Utils.Misc (chunkList)
import Data.Char (isSpace, isNumber)
rotate2DList :: [[a]] -> [[a]]
rotate2DList l = map (\i -> map (!! i) l) [0 .. length l]
parseState :: String -> [[Char]]
parseState = map (dropWhile isSpace) . rotate2DList . map (map (!! 1) . chunkList 4) . init . lines
parseInstructions :: String -> [(Int, Int)]
parseInstructions = concatMap ((\[n, a, b] -> replicate n (a, b)) . map read . filter (isNumber . head) . words) . lines
evaluateState :: [[Char]] -> (Int, Int) -> [[Char]]
evaluateState state (a, b) = newState
where extracted = zipWith (\i l -> (if i == a then tail l else l)) [1..] state
movedChar = head $ state !! (a - 1)
newState = zipWith (\i l -> (if i == b then movedChar : l else l)) [1..] extracted
executeInstructions :: [[Char]] -> [(Int, Int)] -> [[Char]]
executeInstructions state (instruction:xs) = executeInstructions newState xs
where newState = evaluateState state instruction
executeInstructions state [] = state
main = interact $
map head
. (\[state, instructions] -> executeInstructions (parseState state) (parseInstructions instructions))
. map T.unpack . T.splitOn "\n\n" . T.pack

30
5-b.hs Normal file
View File

@ -0,0 +1,30 @@
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text as T
import GHC.Utils.Misc (chunkList)
import Data.Char (isSpace, isNumber)
rotate2DList :: [[a]] -> [[a]]
rotate2DList l = map (\i -> map (!! i) l) [0 .. length l]
parseState :: String -> [[Char]]
parseState = map (dropWhile isSpace) . rotate2DList . map (map (!! 1) . chunkList 4) . init . lines
parseInstructions :: String -> [(Int, Int, Int)]
parseInstructions = map ((\[n, a, b] -> (n, a, b)) . map read . filter (isNumber . head) . words) . lines
evaluateState :: [[Char]] -> (Int, Int, Int) -> [[Char]]
evaluateState state (n, a, b) = newState
where extracted = zipWith (\i l -> (if i == a then drop n l else l)) [1..] state
movedChars = take n $ state !! (a - 1)
newState = zipWith (\i l -> (if i == b then movedChars ++ l else l)) [1..] extracted
executeInstructions :: [[Char]] -> [(Int, Int, Int)] -> [[Char]]
executeInstructions state (instruction:xs) = executeInstructions newState xs
where newState = evaluateState state instruction
executeInstructions state [] = state
main = interact $
map head
. (\[state, instructions] -> executeInstructions (parseState state) (parseInstructions instructions))
. map T.unpack . T.splitOn "\n\n" . T.pack

View File

@ -2,7 +2,7 @@
rm ./*-a
rm ./*-b
rm ./*-a-v*
rm ./*-b-v*
rm ./*-a-v2
rm ./*-b-v2
rm ./*.hi
rm ./*.o