Skipping 3 for a while
parent
13f2a77803
commit
0760edeabc
|
@ -1,25 +1,87 @@
|
|||
-- https://adventofcode.com/2023/day/3
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.IO as T
|
||||
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 "Advent of Code 2023 - Day 3"
|
||||
putStrLn ("Part 1: " <> show (solveP1 entries))
|
||||
putStrLn ("Part 2: " <> show (solveP2 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
|
||||
--
|
||||
|
@ -31,7 +93,7 @@ solveP2 = id
|
|||
-- Examples
|
||||
--
|
||||
|
||||
example :: [[Char]]
|
||||
example :: [Text]
|
||||
example =
|
||||
[ "467..114.."
|
||||
, "...*......"
|
||||
|
|
Loading…
Reference in New Issue