1
0
Fork 0

Minor refactoring - replaced all fmaps with <$> (idk why I kept using fmaps in the first place)

This commit is contained in:
Jonathan Chan 2017-12-19 23:40:38 -08:00
parent 309920939a
commit c3c22a5f8f
14 changed files with 43 additions and 46 deletions

2
01.hs
View File

@ -8,6 +8,6 @@ halfwaySum ns =
main :: IO () main :: IO ()
main = do main = do
nums <- fmap (map (read . pure)) $ readFile "01.txt" nums <- map (read . pure) <$> readFile "01.txt"
print $ circularSum nums print $ circularSum nums
print $ halfwaySum nums print $ halfwaySum nums

2
02.hs
View File

@ -10,6 +10,6 @@ divline ns =
main :: IO () main :: IO ()
main = do main = do
grid <- fmap (map (map read . words) . lines) $ readFile "02.txt" grid <- map (map read . words) . lines <$> readFile "02.txt"
print $ sum . map (\line -> maximum line - minimum line) $ grid print $ sum . map (\line -> maximum line - minimum line) $ grid
print $ sum . map divline $ grid print $ sum . map divline $ grid

2
04.hs
View File

@ -6,7 +6,7 @@ isPassphraseValid ws = sort ws == (toAscList . fromList) ws
main :: IO () main :: IO ()
main = do main = do
passphrases <- fmap (map words . lines) $ readFile "04.txt" passphrases <- map words . lines <$> readFile "04.txt"
let valids = sum $ map (fromEnum . isPassphraseValid) passphrases let valids = sum $ map (fromEnum . isPassphraseValid) passphrases
let stillValids = sum $ map (fromEnum . isPassphraseValid . (map sort)) passphrases let stillValids = sum $ map (fromEnum . isPassphraseValid . (map sort)) passphrases
print $ valids print $ valids

2
05.hs
View File

@ -15,7 +15,7 @@ getExitSteps len f (!steps, i, jumps) =
main :: IO () main :: IO ()
main = do main = do
jumpsList <- fmap (map read . lines) $ readFile "05.txt" jumpsList <- map read . lines <$> readFile "05.txt"
let jumpsMap = fromList $ zip [0..] jumpsList let jumpsMap = fromList $ zip [0..] jumpsList
print $ getExitSteps (length jumpsList) (+1) (0, 0, jumpsMap) print $ getExitSteps (length jumpsList) (+1) (0, 0, jumpsMap)
print $ getExitSteps (length jumpsList) (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap) print $ getExitSteps (length jumpsList) (\v -> if v >= 3 then v - 1 else v + 1) (0, 0, jumpsMap)

2
06.hs
View File

@ -33,5 +33,5 @@ cycles prevCount (prevBank, banks) =
main :: IO () main :: IO ()
main = do main = do
bank <- fmap (fromList . map read . words) $ readFile "06.txt" bank <- fromList . map read . words <$> readFile "06.txt"
print $ cycles 0 (bank, empty) print $ cycles 0 (bank, empty)

14
07.hs
View File

@ -33,19 +33,17 @@ getDiffMinority ns =
parseLine :: String -> (Program, (Weight, Programs)) parseLine :: String -> (Program, (Weight, Programs))
parseLine line = parseLine line =
let nameAndWeight : programsString : _ = splitOn ")" line let nameAndWeight : programsString : _ = splitOn ")" line
name : weight : _ = splitOn " (" nameAndWeight name : weight : _ = splitOn " (" nameAndWeight
programs = discardEmpty . splitOn ", " . last . splitOn " -> " $ programsString programs = discardEmpty . splitOn ", " . last . splitOn " -> " $ programsString
in (name, (read weight, programs)) in (name, (read weight, programs))
getBottom :: Map Program (Weight, Programs) -> [(Program, (Weight, Programs))] -> Program getBottom :: Map Program (Weight, Programs) -> [(Program, (Weight, Programs))] -> Program
getBottom m l = bottomName getBottom m l = bottomName
where where (bottomName, _) : _ = toList $ foldr (\(name, (_, programs)) set ->
(bottomName, _) : _ = toList $ foldr case programs of
(\(name, (_, programs)) set -> [] -> delete name set
case programs of ps -> foldr delete set ps)
[] -> delete name set
ps -> foldr delete set ps)
m l m l
mapToTree :: Map Program (Weight, Programs) -> Program -> Tree Weight mapToTree :: Map Program (Weight, Programs) -> Program -> Tree Weight
@ -66,7 +64,7 @@ findBalanced (Node _ forest) =
main :: IO () main :: IO ()
main = do main = do
programsList <- fmap (map parseLine . lines) $ readFile "07.txt" programsList <- map parseLine . lines <$> readFile "07.txt"
let programsMap = fromList programsList let programsMap = fromList programsList
bottomName = getBottom programsMap programsList bottomName = getBottom programsMap programsList
balanced = findBalanced . cumulate $ mapToTree programsMap bottomName balanced = findBalanced . cumulate $ mapToTree programsMap bottomName

3
08.hs
View File

@ -38,7 +38,6 @@ executeInstruction m (I r v s f) =
main :: IO () main :: IO ()
main = do main = do
input <- readFile "08.txt" maxima <- map (maximum . elems) . tail . scanl executeInstruction empty . map parseLine . lines <$> readFile "08.txt"
let maxima = map (maximum . elems) . tail . scanl executeInstruction empty . map parseLine . lines $ input
print $ last maxima print $ last maxima
print $ maximum maxima print $ maximum maxima

2
11.hs
View File

@ -22,6 +22,6 @@ getDistance (Coordinates x y z) =
main :: IO () main :: IO ()
main = do main = do
coordinates <- fmap (map getCoordinates . splitOn ",") $ readFile "11.txt" coordinates <- map getCoordinates . splitOn "," <$> readFile "11.txt"
print $ getDistance $ fold coordinates print $ getDistance $ fold coordinates
print $ maximum . map getDistance . scanl mappend mempty $ coordinates print $ maximum . map getDistance . scanl mappend mempty $ coordinates

2
12.hs
View File

@ -9,6 +9,6 @@ parseLine str =
main :: IO () main :: IO ()
main = do main = do
graph <- fmap (array (0, 1999) . map parseLine . lines) $ readFile "12.txt" graph <- array (0, 1999) . map parseLine . lines <$> readFile "12.txt"
print $ length $ reachable graph 0 print $ length $ reachable graph 0
print $ length $ scc graph print $ length $ scc graph

2
13.hs
View File

@ -24,6 +24,6 @@ anyCaught firewalls delay =
main :: IO () main :: IO ()
main = do main = do
firewalls <- fmap (map parseLine . lines) $ readFile "13.txt" firewalls <- map parseLine . lines <$> readFile "13.txt"
print $ severity firewalls print $ severity firewalls
print $ findIndex not $ map (anyCaught firewalls) [0..] print $ findIndex not $ map (anyCaught firewalls) [0..]

2
14.hs
View File

@ -30,7 +30,7 @@ sparseHash lengths =
in concat . map (printf "%08b" . foldr xor 0) . chunksOf 16 $ hashed in concat . map (printf "%08b" . foldr xor 0) . chunksOf 16 $ hashed
getEdges :: Int -> (Seq Char, [Edge]) -> (Seq Char, [Edge]) getEdges :: Int -> (Seq Char, [Edge]) -> (Seq Char, [Edge])
getEdges ind (str, edges) = if str ! ind == '0' then (str, edges) else getEdges ind se@(str, edges) = if str ! ind == '0' then se else
let row = ind // 128 let row = ind // 128
col = ind % 128 col = ind % 128
neighbours = [(row + 1, col ), neighbours = [(row + 1, col ),

6
16.hs
View File

@ -15,7 +15,7 @@ exchange x y (s, positions, swaps) =
in (s, insert spunX (positions ! spunY) . insert spunY (positions ! spunX) $ positions, swaps) in (s, insert spunX (positions ! spunY) . insert spunY (positions ! spunX) $ positions, swaps)
partner :: Char -> Char -> State -> State partner :: Char -> Char -> State -> State
partner p q (s, positions, swaps) = partner p q (s, positions, swaps) =
(s, positions, insert p (swaps ! q) . insert q (swaps ! p) $ swaps) (s, positions, insert p (swaps ! q) . insert q (swaps ! p) $ swaps)
spin :: Int -> State -> State spin :: Int -> State -> State
@ -37,12 +37,12 @@ applyDance :: State -> String -> String
applyDance (s, positions, swaps) str = applyDance (s, positions, swaps) str =
let positionsList = snd . unzip . toAscList $ positions let positionsList = snd . unzip . toAscList $ positions
swapsReversed = fromList . (uncurry $ flip zip) . unzip . toList $ swaps swapsReversed = fromList . (uncurry $ flip zip) . unzip . toList $ swaps
in map (swapsReversed !) . (drop (16 - s) <++> take (16 - s)) . map (str !!) $ positionsList in map (swapsReversed !) . (drop (16 - s) <++> take (16 - s)) . map (str !!) $ positionsList
where (f <++> g) p = f p ++ g p where (f <++> g) p = f p ++ g p
main :: IO () main :: IO ()
main = do main = do
moves <- fmap (map parseMove . splitOn ",") $ readFile "16.txt" moves <- map parseMove . splitOn "," <$> readFile "16.txt"
let ip = [0..15]; ap = ['a'..'p'] let ip = [0..15]; ap = ['a'..'p']
state = dance moves (0, fromList $ zip ip ip, fromList $ zip ap ap) state = dance moves (0, fromList $ zip ip ip, fromList $ zip ap ap)
dances = iterate (applyDance state) ap dances = iterate (applyDance state) ap

2
18a.hs
View File

@ -66,6 +66,6 @@ recover instructions (reg, pos, freq, rec) =
main :: IO () main :: IO ()
main = do main = do
instructions <- fmap (fromList . map parseLine . lines) $ readFile "18.txt" instructions <- fromList . map parseLine . lines <$> readFile "18.txt"
let initialState = (V.replicate 5 0, 0, 0, 0) let initialState = (V.replicate 5 0, 0, 0, 0)
print $ recover instructions initialState print $ recover instructions initialState

46
18b.hs
View File

@ -50,43 +50,43 @@ getValue v r = case v of
-- OPERATIONS -- OPERATIONS
sen :: Value -> Instruction sen :: Value -> Instruction
sen v Zero (State p0 p1 s c) = sen v Zero state@(State p0 p1 s c) =
State p0 { state {
position = position p0 + 1 zero = p0 { position = position p0 + 1 },
} p1 { one = p1 { queue = queue p1 |> getValue v (registers p0) },
queue = queue p1 |> getValue v (registers p0) stop = (fst s, False)
} (fst s, False) c }
sen v One state = swap . sen v Zero . swap $ state { count = count state + 1 } sen v One state = swap . sen v Zero . swap $ state { count = count state + 1 }
rcv :: Value -> Instruction rcv :: Value -> Instruction
rcv i Zero (State p0 p1 s c) = rcv i Zero state@(State p0 p1 s c) =
if S.null $ queue p0 then State p0 p1 (True, snd s) c else if S.null $ queue p0 then state { stop = (True, snd s) } else
let (que, val) = pop $ queue p0 let (que, val) = pop $ queue p0
in State p0 { in state { zero = p0 {
registers = registers p0 // [(getIndex i, val)], registers = registers p0 // [(getIndex i, val)],
position = position p0 + 1, position = position p0 + 1,
queue = que queue = que
} p1 s c }}
where pop q = (deleteAt 0 q, q `index` 0) where pop q = (deleteAt 0 q, q `index` 0)
rcv i One state = swap . rcv i Zero . swap $ state rcv i One state = swap . rcv i Zero . swap $ state
app :: (Int -> Int -> Int) -> Value -> Value -> Instruction app :: (Int -> Int -> Int) -> Value -> Value -> Instruction
app f i v Zero (State p0 p1 s c) = app f i v Zero state@(State p0 p1 s c) =
let reg = registers p0 let reg = registers p0
ind = getIndex i ind = getIndex i
val = getValue v reg val = getValue v reg
in State p0 { in state { zero = p0 {
registers = reg // [(ind, reg ! ind `f` val)], registers = reg // [(ind, reg ! ind `f` val)],
position = position p0 + 1 position = position p0 + 1
} p1 s c }}
app f i v One state = swap . app f i v Zero . swap $ state app f i v One state = swap . app f i v Zero . swap $ state
jgz :: Value -> Value -> Instruction jgz :: Value -> Value -> Instruction
jgz condition offset Zero (State p0 p1 s c) = jgz condition offset Zero state@(State p0 p1 s c) =
let reg = registers p0 let reg = registers p0
in State p0 { in state { zero = p0 {
position = position p0 + if getValue condition reg > 0 then getValue offset reg else 1 position = position p0 + if getValue condition reg > 0 then getValue offset reg else 1
} p1 s c }}
jgz condition offset One state = swap . jgz condition offset Zero . swap $ state jgz condition offset One state = swap . jgz condition offset Zero . swap $ state
-- PARSE -- PARSE
@ -123,6 +123,6 @@ getCount instructions state =
main :: IO () main :: IO ()
main = do main = do
instructions <- fmap (fromList . map parseLine . lines) $ readFile "18.txt" instructions <- fromList . map parseLine . lines <$> readFile "18.txt"
let initialState = (State (Program (V.replicate 5 0) 0 empty) (Program (V.replicate 5 0 // [(4, 1)]) 0 empty) (False, False) 0) let initialState = (State (Program (V.replicate 5 0) 0 empty) (Program (V.replicate 5 0 // [(4, 1)]) 0 empty) (False, False) 0)
print $ getCount instructions initialState print $ getCount instructions initialState