Day 8 part 1
This commit is contained in:
parent
c735adea4f
commit
acb4341e9d
@ -91,6 +91,8 @@ executable 8
|
||||
-- other-extensions:
|
||||
build-depends: base ^>=4.18.2.1
|
||||
, split
|
||||
, matrix
|
||||
, extra
|
||||
hs-source-dirs: app
|
||||
default-language: GHC2021
|
||||
executable 9
|
||||
|
69
app/8.hs
69
app/8.hs
@ -1,15 +1,72 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE LambdaCase, MultiWayIf #-}
|
||||
module Main where
|
||||
|
||||
import Data.Functor
|
||||
import Data.Matrix hiding (trace)
|
||||
import Data.List
|
||||
import Numeric.Extra
|
||||
import Debug.Trace
|
||||
|
||||
parse = undefined
|
||||
data Pos = Pos { ch :: Char
|
||||
, ma :: Bool
|
||||
}
|
||||
|
||||
solve1 = undefined
|
||||
instance Show Pos where
|
||||
show (Pos '.' True) = show '#'
|
||||
show (Pos ch _) = show ch
|
||||
|
||||
parse :: String -> Matrix Pos
|
||||
parse = fromLists . (((`Pos` False) <$>) <$>) . lines
|
||||
|
||||
positionsOfChar :: Char -> Matrix Pos -> [(Int,Int)]
|
||||
positionsOfChar c s = zip [1..] (toLists s) >>= \(y,l) -> zip [1..] l >>= \(x,c') ->
|
||||
if c == ch c' then pure (y,x) else mempty
|
||||
|
||||
getMarked :: Matrix Pos -> [(Int,Int)]
|
||||
getMarked s = zip [1..] (toLists s) >>= \(y,l) -> zip [1..] l >>= \(x,c) ->
|
||||
if ma c then pure (y,x) else mempty
|
||||
|
||||
availableChars :: [Char]
|
||||
availableChars = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9']
|
||||
|
||||
dist :: (Int,Int) -> (Int,Int) -> Float
|
||||
dist (y,x) (y',x') = sqrt $ intToFloat (y-y')^2 + intToFloat (x-x')^2
|
||||
|
||||
line :: (Int,Int) -> (Int,Int) -> (Int,Int) -> Bool
|
||||
line (y1,x1) (y2,x2) (y3,x3) =
|
||||
if | x2 == x1 && x3 == x2 -> True
|
||||
| x2 == x1 || x3 == x2 || x1 == x3 -> False
|
||||
| otherwise ->
|
||||
((y2-y1) `div` (x2-x1)) == ((y2-y3) `div` (x2-x3)) &&
|
||||
((y2-y1) `div` (x2-x1)) == ((y1-y3) `div` (x1-x3))
|
||||
|
||||
combo :: Eq a => [a] -> [(a,a)]
|
||||
combo ps = [(a,b) | a <- ps, b <- ps, a /= b]
|
||||
|
||||
|
||||
getAntinodePos :: (Int,Int) -> [(Int,Int)] -> [(Int,Int)]
|
||||
getAntinodePos (i,j) ps =
|
||||
let inbounds (y,x) = and [0 < y, y <= i, 0 < x, x <= j] in
|
||||
nub $ [ c | (p@(y,x),p'@(y',x')) <- combo ps,
|
||||
c <- [(y + (y-y'),x+(x-x')),
|
||||
(y - (y-y'),x+(x-x')),
|
||||
(y + (y-y'),x-(x-x')),
|
||||
(y - (y-y'),x-(x-x'))],
|
||||
inbounds c,
|
||||
line c p p']
|
||||
|
||||
|
||||
mark :: Matrix Pos -> [(Int,Int)] -> Matrix Pos
|
||||
mark = foldr (\p@(y,x) s -> let c = getElem y x s in setElem (c {ma = True}) p s)
|
||||
|
||||
solve1 :: Matrix Pos -> Int
|
||||
solve1 s = length . getMarked $
|
||||
foldr (flip mark . getAntinodePos (nrows s, ncols s) . (`positionsOfChar` s)) s availableChars
|
||||
|
||||
solve2 = undefined
|
||||
|
||||
main :: IO ()
|
||||
main = readFile "inputs/8" <&> parse >>= \i ->
|
||||
print (solve1 i) >>
|
||||
print (solve2 i)
|
||||
main = readFile "inputs/8.example" <&> parse >>= \i ->
|
||||
print (solve1 i)
|
||||
-- >>
|
||||
-- print (solve2 i)
|
||||
|
50
inputs/8
Normal file
50
inputs/8
Normal file
@ -0,0 +1,50 @@
|
||||
.......................V.........e...O............
|
||||
..........q.pj8...............................u...
|
||||
...................8..............................
|
||||
.............8.....6.................J....l....u..
|
||||
........................6................J..Z..B..
|
||||
......e.........E...........................O.J...
|
||||
......Jq..........................5...............
|
||||
...............E...........e.Q..5.f...............
|
||||
..............................Q..A.....f..B.....O.
|
||||
....V...................j.....Af..................
|
||||
............8......n..............l...f....Z7.....
|
||||
...............n..........4........A........BD....
|
||||
...........j...................Q..z.......R....l..
|
||||
N.........6....q.....3....n.........D...........Z.
|
||||
.............a.6..3.F........D..I.................
|
||||
.............03.................Q.......h...2.....
|
||||
......................A.u.......................m.
|
||||
.V........F......L.............5..........z.R....Z
|
||||
.......N....q.................n.......L.E.........
|
||||
..................M.........y.....................
|
||||
......N............................m.L..y........R
|
||||
.o....................L...........I...7..R........
|
||||
......o..........9..............2.......D.........
|
||||
..od.............y...........................I....
|
||||
d........3.....M...........E.............I........
|
||||
......X.W....................p.2.....7...z....s...
|
||||
V......o........M.....9.................G......7..
|
||||
.................M.....................h..0....m..
|
||||
.......d.......F......p.........s.h........z......
|
||||
..r..........Y.i................9............s....
|
||||
.....W..a.Y..........y.............p..............
|
||||
.....g.......r........w...........................
|
||||
....r.....b...............g........x.s.....h......
|
||||
....a.....d.......................................
|
||||
.....................S.......w.............1......
|
||||
..Y...............................H...............
|
||||
...b...........Y........................e..t...0.v
|
||||
..........i..........w.........9....T........v....
|
||||
.................U...........2....................
|
||||
.........S........t......T........................
|
||||
....................U..................Gt.........
|
||||
....U...S..........................P.....1.B......
|
||||
.r...X............w.......P.....x.j...............
|
||||
...W......x..b........g........F.....a............
|
||||
S.i.................................1.......H.....
|
||||
.......U......b......x.....X..........G.1.........
|
||||
...i....X....................P..4........H........
|
||||
.................................H................
|
||||
......W...................T4...g................v.
|
||||
..........................v........GP..4.....t....
|
Loading…
Reference in New Issue
Block a user