2017-12-16 19:09:58 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
|
|
|
import Data.List (foldl')
|
|
|
|
import Data.List.Split (splitOn)
|
|
|
|
import Data.Bits ((.&.))
|
|
|
|
import Data.Function ((&))
|
|
|
|
import Data.Bimap (Bimap, fromList, toAscList, (!), (!>), insert)
|
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
type Programs = Bimap Int Char
|
|
|
|
type State = (Int, Programs)
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
exchange :: Int -> Int -> State -> State
|
|
|
|
exchange x y (s, programs) =
|
|
|
|
let spunX = (x + 16 - s) .&. 15
|
|
|
|
spunY = (y + 16 - s) .&. 15
|
|
|
|
in (s, insert spunX (programs ! spunY) . insert spunY (programs ! spunX) $ programs)
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
partner :: Char -> Char -> State -> State
|
|
|
|
partner p q (s, programs) =
|
|
|
|
(s, insert (programs !> q) p . insert (programs !> p) q $ programs)
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
addSpin :: Int -> State -> State
|
|
|
|
addSpin s' (s, p) = ((s + s') .&. 15, p)
|
|
|
|
|
|
|
|
spin :: Int -> String -> String
|
|
|
|
spin s str = drop (16 - s) str ++ take (16 - s) str
|
|
|
|
|
|
|
|
parseMove :: String -> State -> State
|
2017-12-16 19:09:58 +00:00
|
|
|
parseMove str =
|
2017-12-17 06:30:06 +00:00
|
|
|
case head str of
|
|
|
|
's' -> addSpin . read $ tail str
|
|
|
|
'x' -> let x : y : [] = splitOn "/" $ tail str
|
|
|
|
in exchange (read x) (read y)
|
2017-12-16 19:09:58 +00:00
|
|
|
'p' -> let p : '/' : q : [] = tail str
|
2017-12-17 06:30:06 +00:00
|
|
|
in partner p q
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
dance :: [State -> State] -> State -> State
|
|
|
|
dance moves state = foldl' (&) state moves
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
danceN :: [State -> State] -> State -> Int -> State
|
|
|
|
danceN _ state 0 = state
|
|
|
|
danceN moves state n = let !newState = dance moves state in danceN moves newState (n-1)
|
2017-12-16 19:09:58 +00:00
|
|
|
|
2017-12-17 06:30:06 +00:00
|
|
|
getOrder :: State -> String
|
|
|
|
getOrder (s, programs) = spin s . snd . unzip . toAscList $ programs
|
2017-12-16 19:09:58 +00:00
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = do
|
|
|
|
moves <- fmap (map parseMove . splitOn ",") $ readFile "16.txt"
|
2017-12-17 06:30:06 +00:00
|
|
|
print $ getOrder $ danceN moves (0, fromList $ zip [0..15] ['a'..'p']) 1
|