Skip to content

Commit

Permalink
fix input processing warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
RossPaterson committed Dec 26, 2024
1 parent 006c965 commit 0d9814b
Show file tree
Hide file tree
Showing 12 changed files with 69 additions and 52 deletions.
14 changes: 10 additions & 4 deletions 2015/Day21.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,22 @@ module Main where

import Utilities

-- Input processing

type Input = PlayerState

data PlayerState = Player {
hit_points :: Int,
damage_score :: Int,
armor_score :: Int
}

parse :: String -> PlayerState
parse s = Player h d a
where
[h, d, a] = readNumbers s
parse :: String -> Input
parse s = case readNumbers s of
[h, d, a] -> Player h d a
_ -> error "bad input"

-- Part One

data Item = Item {
name :: String,
Expand Down
5 changes: 3 additions & 2 deletions 2018/Day22.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,12 @@ import Data.Array
type Input = (Int, Position)

parse :: String -> Input
parse s = (runParser depth ld, runParser target lt)
parse s = case lines s of
[ld, lt] -> (runParser depth ld, runParser target lt)
_ -> error "bad input"
where
depth = string "depth: " *> nat
target = (,) <$ string "target: " <*> nat <* char ',' <*> nat
[ld, lt] = lines s

type Position = (Int, Int)

Expand Down
18 changes: 9 additions & 9 deletions 2018/Day24.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,16 +46,16 @@ data AttackType = Fire | Cold | Slashing | Bludgeoning | Radiation
deriving (Show, Eq, Enum, Bounded)

parse :: String -> Input
parse s =
State {
immuneSystem =
makeArmy (map (runParser unit_group) (tail immune_system_lines)),
infection =
makeArmy (map (runParser unit_group) (tail infection_lines))
}
parse s = case paragraphs s of
[p1, p2] ->
State {
immuneSystem =
makeArmy (map (runParser unit_group) (tail (lines p1))),
infection =
makeArmy (map (runParser unit_group) (tail (lines p2)))
}
_ -> error "bad input"
where
ls = lines s
(immune_system_lines, "":infection_lines) = span (not . null) ls
unit_group =
Group <$> nat <* string " units each with " <*> unit_type
unit_type =
Expand Down
5 changes: 3 additions & 2 deletions 2019/Day03.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,10 @@ data Direction = R | U | L | D
deriving (Bounded, Enum, Show)

parse :: String -> Input
parse s = (w1, w2)
parse s = case lines s of
[l1, l2] -> (runParser wire l1, runParser wire l2)
_ -> error "bad input"
where
[w1, w2] = map (runParser wire) (lines s)
wire = sepBy1 segment (char ',')
segment = Segment <$> enumValue <*> nat

Expand Down
14 changes: 8 additions & 6 deletions 2020/Day16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,17 +27,19 @@ data Range = Range Int Int
type Ticket = [Int]

parse :: String -> Input
parse s = Input {
field_rules = map (runParser rule) p1,
your_ticket = runParser ticket (p2!!1),
others = map (runParser ticket) (tail p3)
}
parse s = case map lines (paragraphs s) of
[p1, p2, p3] ->
Input {
field_rules = map (runParser rule) p1,
your_ticket = runParser ticket (p2!!1),
others = map (runParser ticket) (tail p3)
}
_ -> error "bad input"
where
rule = (,) <$> some (satisfy (/= ':')) <* string ": " <*> ranges
ranges = (,) <$> range <* string " or " <*> range
range = Range <$> nat <* char '-' <*> nat
ticket = sepBy1 nat (char ',')
[p1, p2, p3] = map lines (paragraphs s)

-- Part One

Expand Down
5 changes: 3 additions & 2 deletions 2020/Day20.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,10 @@ parse :: String -> Input
parse = Map.fromList . map parseCamera . paragraphs

parseCamera :: String -> (Int, Tile)
parseCamera s = (runParser tileno header, parseTile rest)
parseCamera s = case lines s of
header:rest -> (runParser tileno header, parseTile rest)
_ -> error "bad input"
where
header:rest = lines s
tileno = string "Tile " *> nat <* char ':'

parseTile :: [String] -> Tile
Expand Down
5 changes: 3 additions & 2 deletions 2020/Day22.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,10 +14,11 @@ type Decks = (Deck, Deck)
type Deck = Seq Int

parse :: String -> Input
parse s = (numbers p1, numbers p2)
parse s = case paragraphs s of
[p1, p2] -> (numbers p1, numbers p2)
_ -> error "bad input"
where
numbers = Seq.fromList . map read . tail . lines
[p1, p2] = paragraphs s

-- Part One

Expand Down
12 changes: 6 additions & 6 deletions 2020/Day25.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,9 @@ import Number
type Input = (Int, Int)

parse :: String -> Input
parse s = (x, y)
where
x:y:_ = map read (lines s)
parse s = case map read (lines s) of
[x, y] -> (x, y)
_ -> error "bad input"

-- Part One

Expand All @@ -28,9 +28,9 @@ base = 7
--
-- find the value c ^ log_d = base ^ (log_d*log_c) = d ^ log_c.
solve1 :: Input -> Int
solve1 (d, c) = modularPower modulus c log_d
where
Just log_d = modularLogarithm modulus base d
solve1 (d, c) = case modularLogarithm modulus base d of
Just log_d -> modularPower modulus c log_d
Nothing -> error "no solution"

testInput :: String
testInput = "\
Expand Down
7 changes: 4 additions & 3 deletions 2021/Day13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,14 +14,15 @@ data Fold = FoldX Int | FoldY Int
type Input = ([Position], [Fold])

parse :: String -> Input
parse s =
(map (runParser pos) (lines sp), map (runParser fold_instr) (lines sf))
parse s = case paragraphs s of
[sp, sf] ->
(map (runParser pos) (lines sp), map (runParser fold_instr) (lines sf))
_ -> error "bad input"
where
pos = Position <$> nat <* char ',' <*> nat
fold_instr =
FoldX <$ string "fold along x=" <*> nat <|>
FoldY <$ string "fold along y=" <*> nat
[sp, sf] = paragraphs s

-- Part One

Expand Down
13 changes: 7 additions & 6 deletions 2021/Day20.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,13 @@ type Pixels = Set Position
type Input = (Algorithm, Pixels)

parse :: String -> Input
parse s = (algo, pixels)
where
[p1, p2] = paragraphs s
algo = Set.fromList
[n | (n, c) <- zip [0..] (filter (/= '\n') p1), c == '#']
pixels = Set.fromList [p | (p, c) <- readGrid p2, c == '#']
parse s = case paragraphs s of
[p1, p2] -> (algo, pixels)
where
algo = Set.fromList
[n | (n, c) <- zip [0..] (filter (/= '\n') p1), c == '#']
pixels = Set.fromList [p | (p, c) <- readGrid p2, c == '#']
_ -> error "bad input"

-- Part One

Expand Down
5 changes: 3 additions & 2 deletions 2021/Day21.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,10 @@ import qualified Data.Map as Map
type Input = (Int, Int)

parse :: String -> Input
parse s = (runParser startPos l1, runParser startPos l2)
parse s = case lines s of
[l1, l2] -> (runParser startPos l1, runParser startPos l2)
_ -> error "bad input"
where
[l1, l2] = lines s
startPos = string "Player " *> digit *> string " starting position: " *> nat

-- Part One
Expand Down
18 changes: 10 additions & 8 deletions 2022/Day22.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,17 @@ data FieldMap = FieldMap {
deriving (Show)

parse :: String -> Input
parse s = (field_map, runParser path path_line)
parse s = case paragraphs s of
[map_text, path_text] -> (field_map, runParser path path_line)
where
field_map = FieldMap {
open = Set.fromList [p | (p, c) <- pcs, c == '.'],
walls = Set.fromList [p | (p, c) <- pcs, c == '#']
}
pcs = readGrid map_text
path_line = head (lines path_text)
_ -> error "bad input"
where
field_map = FieldMap {
open = Set.fromList [p | (p, c) <- pcs, c == '.'],
walls = Set.fromList [p | (p, c) <- pcs, c == '#']
}
pcs = readGrid map_text
[map_text, path_text] = paragraphs s
path_line = head (lines path_text)
path = (,) <$> nat <*> many ((,) <$> enumValue <*> nat)

-- Part One
Expand Down

0 comments on commit 0d9814b

Please sign in to comment.