Skip to content

Instantly share code, notes, and snippets.

@shapr
Created October 11, 2018 17:54
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save shapr/f4c9f2a1d6d269f404277ae3bd89afdd to your computer and use it in GitHub Desktop.
Save shapr/f4c9f2a1d6d269f404277ae3bd89afdd to your computer and use it in GitHub Desktop.
advent of code 2017 , solution for part 1 of day 16
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Applicative
import Data.Attoparsec.Text hiding (take)
import Data.Maybe
import Data.Monoid
import qualified Data.Sequence as S
import qualified Data.Text.IO as TIO
main :: IO ()
main =
do contents <- TIO.readFile "input16.txt"
let ns = parseOnly (pDance `sepBy` char ',') contents
is = fromRight ns
print $ foldl step initstate is
fromRight (Right r) = r
data Dance = Spin Int | Exchange Int Int | Partner Char Char deriving (Show, Eq, Ord)
-- x5/8,pf/e,s10,x7/14,pl/p,x8/1,s8,x10/9,s3,x8/4
pDance = Spin <$ char 's' <*> decimal
<|> Exchange <$ char 'x' <*> decimal <* char '/' <*> decimal
<|> Partner <$ char 'p' <*> anyChar <* char '/' <*> anyChar
initstate = S.fromList ['a'..'p']
step :: S.Seq Char -> Dance -> S.Seq Char
step state (Partner c1 c2) =
let c1pos = fromJust $ S.elemIndexL c1 state
c2pos = fromJust $ S.elemIndexL c2 state
in S.update c1pos c2 (S.update c2pos c1 state)
step state (Exchange n1 n2) =
let c1 = state `S.index` n1
c2 = state `S.index` n2
in S.update n1 c2 $ S.update n2 c1 state
step state (Spin n) = -- spin 3 means the last three are on the front, so drop length - 3 after
let sl = length state in
S.take sl $ S.drop (sl - n) $ S.cycleTaking (sl * 2) state
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment