1
0
Fork 0

Compare commits

...

2 Commits

Author SHA1 Message Date
Bill Ewanick 0760edeabc Skipping 3 for a while 2023-12-09 12:17:57 -05:00
Bill Ewanick 13f2a77803 Start Day 3 2023-12-06 15:31:15 -05:00
2 changed files with 248 additions and 0 deletions

View File

@ -0,0 +1,108 @@
-- https://adventofcode.com/2023/day/3
{-# LANGUAGE OverloadedStrings #-}
import Data.Bifunctor
import Data.List
import Data.Char
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Debug.Trace (trace)
main :: IO ()
main = do
entries <- T.lines <$> T.readFile "src/advent_of_code/2023/input3"
putStrLn "Advent of Code 2023 - Day 3"
putStrLn ("Part 1: " <> show (solveP1 entries))
-- putStrLn ("Part 2: " <> show (solveP2 entries))
--
-- Part 1
--
allCoords :: Int -> [(Int, Int)]
allCoords n = [ (x,y) | x <- [0..n-1], y <- [0..n-1]]
getSymbolSet :: [Text] -> String
getSymbolSet = nub . concatMap
(filter (\str
-> not (isDigit str)
&& (/= '.') str
) . T.unpack)
nextCoord :: [(Int, Int)]
nextCoord = [ (x,y) | x <- [-1,0,1], y <- [-1,0,1] ]
adjacentCoords :: Int -> (Int, Int) -> [(Int, Int)]
adjacentCoords l (x,y) =
filter (and . tupleToList . bimap gtl gtl)
. filter (and . tupleToList . bimap gtz gtz)
$ map (bimap (+x) (+y)) nextCoord
where
gtz = (>=0)
gtl = (< l)
tupleToList (a, b) = [a,b]
pointer :: [Text] -> String -> (Int, Int) -> Int
pointer txt symbolSet (x,y) = numberAt symbolSet x $ txt !! y
numberAt :: String -> Int -> Text -> Int
numberAt symbolSet n txt = if not $ check (T.head h')
then 0
else sumPair . bimap
(T.takeWhileEnd check)
(T.takeWhile check)
$ (h,h')
where
isElem = flip elem symbolSet
check a = a /= '.' && not (isElem a)
(h,h') = T.splitAt n txt
sumPair :: (Text, Text) -> Int
sumPair (a,b) = read str'
where
str = T.unpack $ T.concat [a,b]
str' = if null str then "0" else str
-- attachCoords :: [Text] -> [((Int, Int), Char)]
-- attachCoords = concat . zipWith (\col -> map (\(r,c) -> ((r,col),c))) [0..] . map (zip [0..] . T.unpack)
attachCoords :: [Text] -> [[((Int, Int), Char)]]
attachCoords = zipWith (\col -> map (\(r,c) -> ((r,col),c))) [0..] . map (zip [0..] . T.unpack)
solveP1 = id
getAllNumbers :: [Text] -> [Int]
getAllNumbers = map (read . T.unpack) . concatMap (filter (not . T.null) . T.split (not . isDigit))
test = groupBy (\((i,_),c) ((j,_),c')
-> trace ("\n" <> show c <> show i <> ", " <> show c' <> show j <> "\n")
i == j-1
) $ concatMap (filter (\(_,c)-> isDigit c)) $ attachCoords example
--
-- Part 2
--
solveP2 = id
--
-- Examples
--
example :: [Text]
example =
[ "467..114.."
, "...*......"
, "..35..633."
, "......#..."
, "617*......"
, ".....+.58."
, "..592....."
, "......755."
, "...$.*...."
, ".664.598.."
]

View File

@ -0,0 +1,140 @@
...317..........214.....................................751.................................630...479..205....41.993............416.........
...*....813........%....572........%...629.154......518....*....365..................-.......*.......#.....................422...........661
269.......*...58...........=......264.....*..........*......937.-...........235...303.........848..............195.....154*.........144.-...
........476..@...162.855................$....288...821..............107.....-...........290......../..301.........=...........135..*........
618.............=....*...547...........441....*........................@................*........851....+...................+..*...102.310..
...*961....905......534..$...377...............854...341.342....485.......109....89.995..927..............................90..997......*....
............*...................*.................../.....*......@...........%....*...*.......................+44.....913.........9.....891.
....62......724...592....946.878...854....$.701............480......575.246....119.....54..296.906..684..................*.........*838.....
.................+......*...............478....................469.....*..................*...........+..502..156.........821...........983.
....................315.764..996..571...............=........................804.......&...892....958.....*......*.............61...........
........+...697*.....+.........*...*...........@.448........................*.......322.............*....309..37.602.....775....*...........
32.480..665.....557......+...435..449..691..327....................#....921..535..........755...43...597........................322..7......
......*.....848.........745.............*.......679/............106.......&........404......+....*...................888..750........*......
......93...*....=.............*297......550...........324.597............................................819.....997*......-...734$..588....
.........363..112..754...............&..........723....................14..954.............175....773...*.............&.....................
..................*.......#..........502......../...............606.........@..778*.......#.........*....844...713...743....-.........&.....
............827.895.-539...469...938...../.248.....................*.49............749.............783.........$...+.........33....471......
..............*.................../...517...&......368*710......432...*............................................841.=.................194
.....*491....395.......&481.................../.#...................83................668..181.....698..155*...........981.200..............
...................219.................196.473..224.....=.....733*.......=.........98*.......*.420..........671.....*......*......369.205...
........@......696*....669.....50.....................853.593.........168....@.............802..*...388............3......792........*......
......641............./....62..*...836#.......*169.........@...............872.................416....*.................-...................
..........................#...377..........179.......101........+504.................*554.............947..............447.............830..
243........*902.....#................480*...........+.....*258.........*243.......389.......&....................723.........838...991......
........182.........33..........840......616.733.......756..........290.....................145..119..........................+......&......
..............................................*....807...................777......+..556............@....85#................................
.212.664..3......316..579..462..............435.......*............@....*........36...$........572................703..732........@.........
...........=....@.....*.....*............*.......-..337......656...411.357.373.....................*21....37.........%./.....918...185.387..
...350.................338...161.856..157.906...527...........*............+.........*336.......204............755.............*............
....&...........683...................................801......313............831.230......374.......................383.....940.48.........
...............*........447......635....335......%.........627........44@..........................895....................@.................
....$....958..943.......#...935.%..........*...794......16.*..................+...........100..469........743.*.........529....=.......883..
..308.....*........*776.......*.....*....430............*..562.......895......765.................*.........*..776..........246..921&.......
.........200...............*..1....572................814...........$......#..........138...&....487..668..58.......485.....................
...*845.............935...958.................................667.....%.121.......691.......245.........*..............*........131.........
.........*............*.............=............................*.593.............*..................380........189...219.211......@.......
.....152..783........634...........521.+.......26.............659...............328...%.............................*........$......397.*...
......*.......124..........299..........808.....*........359................424.....%..454..........553.............49..562.....257......723
......641.........24.............576.............975........=..............*.......974.............*...........146......*......../...@......
940.........&....@....221........*.........149.......&...............689....418...........538...................*.....985............526....
.............192.........*816...582...561..+..........915..981%.......*..................*......&8....+.........497..........145............
.........144........$....................@......................425.933....846*824.$...370.342*....375...641..=........927.....*.......160..
............$.......925...67.655....57.............=905..881....@..................585.........746.............224..........224...864...*...
.....872................#..*...$.....*.........#............*...........979....699...................947.........................*.....788..
............949......676..42........340.....694...144......712..296..45...*.......*..............191.@.......889-......=786.....417.........
...........*.................846....................*..160.......*.......403.....347...914.91...=...........................................
.371.=....904.643......816...*...647...$.858.......431..........486..........706......*....-..............961........................698....
......398.....*....252*....591..../..224...$..341...........#................*................956............*...27..............57.....*534
.............363...............................&.............69........163.233.580....113*367..............44...*..................*406.....
...893..457..........91%........................................538.....$......*..............................475....864.......289..........
..........-........................549............909..572.....-..............385.............97.....................=.....159..*...........
...174...............................*...576.875....*.....=...................................*....506..115...............*....856....408...
.....=.......685....58........177.965...-.....*....489......402/..&603.....................357......=..&....84.....451&.810........93...*...
.....................*...87.........................................................447........@............*................-......*...117.
......205.593........298..................................622....955.......34*325......*....965...................604......729....509.......
........=..*.......+...............966.......................$.$...................206......................99....-....424..............$...
378..........636..141.543%....34...........437-.................303.........80....*.............915...........*........*...885...........148
............*................=......................39......-.......208.560*...906...................320.860.975....532....*.........740....
....834...13...................426.395*962...44.......-......552...................*539.+........953.......%............647.........*.......
..............589...............*..........................................179...71.....207........#.577......758...247..........958........
....930.......*......&139...820.56.....%164....................536.=31......*.............................................89................
.....#.........569............*.............882....296......&................465.......21............=.....331........998*..................
..........847..............206....$............%.....#.464.318..=.....751*........................501..971...*..............227.......854...
.466......*......768..../.......110......................*.......612......551......868.......727.......*......39.850..-.....*.........*.....
.........377.561....&.718...94............246..........159...........255............%.........*...........445........472...520.......304.472
...............*..........................@.....292.............................476......&.........135......*...223.........................
..............288.....................944........*......775*934................+......152.............*55..806............239#..............
...181*552...............................*....238...............499...880.476...................................417.#66.........472.........
.....................*........%...629.853............*......@9...@......=.....443...673........271...*..........-...........98..............
.........567*288...10.257..837......*.........862..14................21......*...................%..714...........963.........%.450....528..
....................................862..................889.....604...*424..350...812..34........................*...646...................
...............*....*933.....355@..................*528....=......................+.....*...&996..493.....992..840.......*..271.............
..............984...............................678.................+571.....648......262............*......*..............*......293..197..
..........386..............463..984......129................-588..............*..361...............408..269.652...........406........*..+...
.........*............494....*.......847...*..#..942..825.............&......32.........................*........427...........-....339.....
.......415.=434..439.....*..23........$..34..410.........+.......746.976.............731..../.1*.........709.......*.........197........#...
................*......493.......760.............................................654*....398.........158....../......396.............922....
.....845.=....955...................*.....*574....954*........@...........$.......................-....*.....796......-...426...$732........
.......*.88.............@.........738..924............213...40....115......315...................299...108...................*.......320....
....567...............%..13.................*14...........$.......@.....%.........../...518.......................-.810...514..952..........
........892...275....485.......820.......367.......@.....544...........428.........54..-.............*....108..964...*..........*...........
.......@...................861......#.........893.116.........836.982......961.............../...615.188.....*.....914.........761....765...
...........169.962.........*......81...769...#...............................-..714.424..759.390...@.........855...........562.........*....
....../906......../......81..968.......-..............................185..............*.%............=......................*.205.....72...
................*............*....110........./.907....241.......708...*...383.701..869...............346..............649.771.#............
.............531.976...670...288...........382....*.......*116.........820.-...*............764..556...........@..984....$.......638...165..
........................-..........479.............55..........................515.....345...#................533...*.......................
.....$....569.936.301.........914..*.......-.....=................453..............209..*..........................551.-.......479..........
..233.....*......*.....506.........931..246....221.639....#..................@......*....784........591.................818...%.......523...
.......233....%.........................................416...714&........448.......698......387........432............................*....
...........718.......@......465....................430........................603.......491..*..........*...22.164...+...............179....
...............450.462.549.=....283.185...880......................652.......................142..430.372.....*.......633...................
.370....143....*.........*.........*......*.....962...........*.....*....................537........%...........&136........................
.....39.......956......213...........476.143.......*.......321.60....708..........966.......#...921......+146............+...665............
...........................941...321*.............880.499...........................*.............*.383........668.....212...*....827*428...
..236..527...................=..........................*........../..854......................489...-........................234...........
.....*.................................622..........289..599....207...*............&953.599=...............885............682.....914.....12
793...754.............$497..............*............*................163....................+.........15.....*..*....338*..................
...*.......864................348..........758.......439...................1........83....748...............325.535...................=.....
...368....*........382*250....*.....317.......*................473*....877.+.........*..................@................%....331..513......
.........55..239...........2...377...=......1.792...294*607........831..........*.950...&....-....#....864.....139.......512................
....427.......*...*...#....%...........765...............................418.995.........6..492.465...........@....................*218.....
......*......939.410.371......#...-......#.................&............*.............................496..........503..........629.........
.....410....................215.193.................678.786.....370...71..598......329..........262.................*.......473.............
.........979..855..432=................212.....346..*....................*........*............#...................249...=.....+...525.217..
.........*....*...............387.....*...........*.228......./....%....245..&.....690.....429............................685.........*.....
129....907.423........949.772......666....173..679........992.313...398......427..............*...................244.......................
.........................*.....*............................*........................../....998..........510..825*..........................
.....132....867........%.....42.780..............776*744...898.......664....196....360..823......899.211..=.................+...............
.....*.......%......703................916...%...............................*....*................*....&.....689..$......591.......64*238..
...684..160.......................445.....*...164.......602....249...........431.12.............=..758............138..........983..........
..........@..766.92..............*......334........671..*...............&646..................797.............950.........935.........469...
................*..................510..............*..285..........................................650.......*....807...*............#.....
..205.669...768...88........................+59..148............682........#.................3..............376...*.......191...............
.........&....*..%........................................183......*......61................/........657..........163............255........
..674.......46..............392..251....507.................*.248...74..........+...775.97.....222.........%..........135...950.....*.......
....*...........*967..533...*............*......949..245.276...#.........*.....728...................677..137.....*.....*..&........522.....
...367.......196.......$..239..........510.748..*............/...481..722....................800........*........735..268...................
.........442...................111...............752........567...*.........*..........696..%............790................................
.............182....677..613............................/..........814...372.86........*......915*..............799.................*....253
....&....739*........../....*206.........284...........584...427................727..485..........781.992.........-...............619.......
.....603.........................907........*....607......../.............................617............*...=.......986-.............918...
.........819..667..341...........*....#..397................................#........$..................822...20...........359.....43.......
.......&....*...#....*.......*....88.691.........................700.675....910...227........350...&591............301.......$.......*......
..404$..259.......557....876.218...........216.=211.7...=569........*........................=.................320..*....462...480....747...
..........................+.............#..*........*.................=518........................274............@...276........../.........
.......#...904......622..............923....543....969../..................571..778......#888.253..................+.....163.........-679...
295.207.........708......................................942...496....#...*.......*.373@.......*..645...............580.......177...........
................................982*317............304........*.......28.823....994.......370..96........@.=...*675............*.....604....
644.138.522......%......901.................374*..*.........458.....................#135....=..........730.355........955...=.47.277*.......
...*....*.........288..*.............+.433.........240.................317/........................609............#90.*...623...............
.....%..675....87.......110...126.408..*......355.............................@131......110....778...*..519.834.......537.....19........502.
..831............*460........*..........824.....*..751...467.829..........850..........*............365....*................................
..........398..............473....-..........751.....*......*................@.446*....780...........................732....................
.......................#.........333..................170........596...............943......66..186......@...........@.....=................
......124....780.....58.....933........926.../.............693...*..........*828...............*........666.............=..337..............
.......*.........197..........$.......*......67............-...335...........................122...582................197..........328......
.....151...............................763......180....@............890../....835...578..871..........*295..#....%...........-541.$.........
........................153.........-........@.....*...661..*833......*.775.....-...........................40....665...............701.....
..890....252......................544........809..425..............925......................................................................