diff --git a/y2020/.gitignore b/haskellAoC/.gitignore similarity index 50% rename from y2020/.gitignore rename to haskellAoC/.gitignore index 03c338c..d22cd58 100644 --- a/y2020/.gitignore +++ b/haskellAoC/.gitignore @@ -1,3 +1,4 @@ .stack-work/ *~ -*.cabal \ No newline at end of file +inputs/ +*.cabal diff --git a/haskellAoC/ChangeLog.md b/haskellAoC/ChangeLog.md new file mode 100644 index 0000000..eba731f --- /dev/null +++ b/haskellAoC/ChangeLog.md @@ -0,0 +1,3 @@ +# Changelog for haskellAoC + +## Unreleased changes diff --git a/y2020/LICENSE b/haskellAoC/LICENSE similarity index 97% rename from y2020/LICENSE rename to haskellAoC/LICENSE index e095992..1d915ca 100644 --- a/y2020/LICENSE +++ b/haskellAoC/LICENSE @@ -1,4 +1,4 @@ -Copyright Xavier Morel (c) 2019 +Copyright Xavier Morel (c) 2020 All rights reserved. diff --git a/haskellAoC/README.md b/haskellAoC/README.md new file mode 100644 index 0000000..8c11810 --- /dev/null +++ b/haskellAoC/README.md @@ -0,0 +1 @@ +# haskellAoC diff --git a/y2019/Setup.hs b/haskellAoC/Setup.hs similarity index 100% rename from y2019/Setup.hs rename to haskellAoC/Setup.hs diff --git a/y2019/app/Main.hs b/haskellAoC/app/Main.hs similarity index 50% rename from y2019/app/Main.hs rename to haskellAoC/app/Main.hs index d7565bd..8b3b92f 100644 --- a/y2019/app/Main.hs +++ b/haskellAoC/app/Main.hs @@ -1,6 +1,6 @@ module Main where -import DayPicker +import Lib main :: IO () -main = dayPicker +main = pickYear diff --git a/y2020/package.yaml b/haskellAoC/package.yaml similarity index 80% rename from y2020/package.yaml rename to haskellAoC/package.yaml index 4640b30..1fa9742 100644 --- a/y2020/package.yaml +++ b/haskellAoC/package.yaml @@ -1,10 +1,10 @@ -name: y2020 +name: haskellAoC version: 0.1.0.0 -github: "mx42/y2020" +github: "mx42/haskellAoC" license: BSD3 author: "Xavier Morel" maintainer: "morelx42@gmail.com" -copyright: "2019 Xavier Morel" +copyright: "2020 Xavier Morel" extra-source-files: - README.md @@ -17,19 +17,20 @@ extra-source-files: # To avoid duplicated efforts in documentation and dealing with the # complications of embedding Haddock markup inside cabal files, it is # common to point users to the README.md file. -description: Please see the README on GitHub at +description: Please see the README on GitHub at dependencies: - base >= 4.7 && < 5 +- containers - sort - split -- containers +- directory library: source-dirs: src executables: - y2020-exe: + haskellAoC-exe: main: Main.hs source-dirs: app ghc-options: @@ -37,10 +38,10 @@ executables: - -rtsopts - -with-rtsopts=-N dependencies: - - y2020 + - haskellAoC tests: - y2020-test: + haskellAoC-test: main: Spec.hs source-dirs: test ghc-options: @@ -48,4 +49,4 @@ tests: - -rtsopts - -with-rtsopts=-N dependencies: - - y2020 + - haskellAoC diff --git a/y2019/src/Geo/Point.hs b/haskellAoC/src/Geo/Point.hs similarity index 100% rename from y2019/src/Geo/Point.hs rename to haskellAoC/src/Geo/Point.hs diff --git a/y2019/src/Geo/Segment.hs b/haskellAoC/src/Geo/Segment.hs similarity index 100% rename from y2019/src/Geo/Segment.hs rename to haskellAoC/src/Geo/Segment.hs diff --git a/y2019/src/Geo/Vector.hs b/haskellAoC/src/Geo/Vector.hs similarity index 100% rename from y2019/src/Geo/Vector.hs rename to haskellAoC/src/Geo/Vector.hs diff --git a/haskellAoC/src/Lib.hs b/haskellAoC/src/Lib.hs new file mode 100644 index 0000000..cca2d46 --- /dev/null +++ b/haskellAoC/src/Lib.hs @@ -0,0 +1,58 @@ +module Lib (pickYear) where + +import Y2019.Days +import Y2020.Days + +import Data.List + +import System.Directory +import System.Environment + +type DayFun = [String] -> (String, String) + +getDayFun :: String -> String -> DayFun +getDayFun "2019" "01" = y19day01 +getDayFun "2019" "02" = y19day02 +getDayFun "2019" "03" = y19day03 +getDayFun "2019" "04" = y19day04 +getDayFun "2019" "05" = y19day05 +getDayFun "2019" "06" = y19day06 +getDayFun "2019" "07" = y19day07 +getDayFun "2019" "08" = y19day08 +getDayFun "2019" "09" = y19day09 +getDayFun "2019" "10" = y19day10 +getDayFun "2019" "11" = y19day11 +getDayFun "2019" "12" = y19day12 +getDayFun "2019" "13" = y19day13 +getDayFun "2020" "01" = y20day01 +getDayFun "2020" "02" = y20day02 +getDayFun "2020" "03" = y20day03 + +callDailyFun :: String -> DayFun -> String -> IO () +callDailyFun year fn name = do + putStrLn $ "With input " ++ name + input <- readFile ("inputs/" ++ year ++ "/" ++ name) + let (part1, part2) = fn $ lines input + putStrLn $ "Part1: " ++ part1 + putStrLn $ "Part2: " ++ part2 + +getFiles :: String -> String -> IO [String] +getFiles year day = listDirectory ("inputs/" ++ year ++ "/") >>= + return . filter (isPrefixOf day) + +dayPicker :: String -> String -> IO () +dayPicker year day = do + let dailyFun = getDayFun year day + files <- getFiles year day + _ <- mapM (callDailyFun year dailyFun) files + putStrLn $ "Ending process" + + +load :: [String] -> IO () +load (year:day:_) = dayPicker year day +load _ = putStrLn "Usage: script [year] [day]" + +pickYear :: IO () +pickYear = do + args <- getArgs + load args diff --git a/haskellAoC/src/Y2019/Day01.hs b/haskellAoC/src/Y2019/Day01.hs new file mode 100644 index 0000000..26c114a --- /dev/null +++ b/haskellAoC/src/Y2019/Day01.hs @@ -0,0 +1,17 @@ +module Y2019.Day01 (day1) where + +massFuelReq :: Integer -> Integer +massFuelReq mass = (floor (fromIntegral mass / 3)) - 2 + +moduleFuelReq :: Integer -> Integer +moduleFuelReq mass + | req > 0 = req + moduleFuelReq req + | req <= 0 = 0 + where req = massFuelReq mass + +day1 :: [String] -> (String, String) +day1 input = (part1, part2) + where + modules = (map read input) + part1 = show $ sum $ map massFuelReq modules + part2 = show $ sum $ map moduleFuelReq modules diff --git a/y2019/src/Day2.hs b/haskellAoC/src/Y2019/Day02.hs similarity index 64% rename from y2019/src/Day2.hs rename to haskellAoC/src/Y2019/Day02.hs index 45e2e27..ccfe69e 100644 --- a/y2019/src/Day2.hs +++ b/haskellAoC/src/Y2019/Day02.hs @@ -1,6 +1,6 @@ -module Day2 (day2) where +module Y2019.Day02 (day2) where -import Intcode +import Y2019.Intcode replaceNth :: Int -> a -> [a] -> [a] replaceNth _ _ [] = [] @@ -19,17 +19,9 @@ bruteforce noun verb input objective | noun < 100 = bruteforce noun (verb + 1) input objective where result = computeVerbNoun noun verb input -day2 :: IO () -day2 = do - putStrLn "AoC 2019 day 2" - putStr "Enter input >" - input <- getLine - putStrLn "" - let intCodes = parseProgram input - - putStr "Part 1: " - print (computeVerbNoun 12 2 intCodes) - - putStr "Part 2: " - let objective = 19690720 - print (bruteforce 0 0 intCodes objective) +day2 :: [String] -> (String, String) +day2 (input:_) = (part1, part2) + where intCodes = parseProgram input + part1 = show $ computeVerbNoun 12 2 intCodes + objective = 19690720 + part2 = show $ bruteforce 0 0 intCodes objective diff --git a/y2019/src/Day3.hs b/haskellAoC/src/Y2019/Day03.hs similarity index 75% rename from y2019/src/Day3.hs rename to haskellAoC/src/Y2019/Day03.hs index edbb4c4..a6fc16e 100644 --- a/y2019/src/Day3.hs +++ b/haskellAoC/src/Y2019/Day03.hs @@ -1,4 +1,4 @@ -module Day3 (day3) where +module Y2019.Day03 (day3) where import Data.List.Split import Data.List @@ -55,30 +55,13 @@ getDistanceOnShape [] _ = 0 getIntersectionDist :: [Segment] -> [Segment] -> Point -> Int getIntersectionDist s1 s2 p = getDistanceOnShape s1 p + getDistanceOnShape s2 p -day3 :: IO () -day3 = do - putStrLn "AoC 2019 day 3" - putStr "Enter input >" - - firstInput <- getLine - secondInput <- getLine - putStrLn "" - - let firstShape = parseSegments firstInput - let firstCoords = getCoordsFromSegs firstShape - let secondShape = parseSegments secondInput - let secondCoords = getCoordsFromSegs secondShape - - let intersections = computeIntersections firstCoords secondCoords - - let part1 = manhattanDist origin (head (sortOn (manhattanDist origin) intersections)) - putStr "Part1: " - print part1 - putStrLn "" - - let intersectionDists = map (getIntersectionDist firstShape secondShape) intersections - let part2 = minimum intersectionDists - - putStr "Part2: " - print part2 - putStrLn "" +day3 :: [String] -> (String, String) +day3 (firstInput:secondInput:_) = (part1, part2) + where firstShape = parseSegments firstInput + firstCoords = getCoordsFromSegs firstShape + secondShape = parseSegments secondInput + secondCoords = getCoordsFromSegs secondShape + intersections = computeIntersections firstCoords secondCoords + part1 = show $ manhattanDist origin (head (sortOn (manhattanDist origin) intersections)) + intersectionDists = map (getIntersectionDist firstShape secondShape) intersections + part2 = show $ minimum intersectionDists diff --git a/haskellAoC/src/Y2019/Day04.hs b/haskellAoC/src/Y2019/Day04.hs new file mode 100644 index 0000000..36e3266 --- /dev/null +++ b/haskellAoC/src/Y2019/Day04.hs @@ -0,0 +1,24 @@ +module Y2019.Day04 (day4) where + +import Data.List.Split +import Data.List + +isValid :: (Int -> Bool) -> Int -> Bool +isValid groupsCriteria n = length6 && isSorted && hasGroups + where digits = show n + length6 = (length digits) == 6 + isSorted = digits == sort digits + hasGroups = any (\d -> groupsCriteria (length d)) (group digits) + +getNext :: (Int -> Bool) -> Int -> Int +getNext groupsCriteria cur + | isValid groupsCriteria (cur + 1) = (cur + 1) + | otherwise = getNext groupsCriteria (cur + 1) + +day4 :: [String] -> (String, String) +day4 (input:_) = (part1, part2) + where range = (map read (splitOn "-" input)) :: [Int] + iterP1 = takeWhile (< (range !! 1)) (iterate (getNext (> 1)) (range !! 0)) + part1 = show ((length iterP1) - 1) + iterP2 = takeWhile (< (range !! 1)) (iterate (getNext (== 2)) (range !! 0)) + part2 = show ((length iterP2) - 1) diff --git a/haskellAoC/src/Y2019/Day05.hs b/haskellAoC/src/Y2019/Day05.hs new file mode 100644 index 0000000..59de7b6 --- /dev/null +++ b/haskellAoC/src/Y2019/Day05.hs @@ -0,0 +1,11 @@ +module Y2019.Day05 (day5) where + +import Y2019.Intcode + +day5 :: [String] -> (String, String) +day5 (input:_) = (part1, part2) + where intCodes = parseProgram input + outputP1 = runProgramV2 [1] intCodes + part1 = show $ outputP1 !! 0 + outputP2 = runProgramV2 [5] intCodes + part2 = show $ outputP2 !! 0 diff --git a/y2019/src/Day6.hs b/haskellAoC/src/Y2019/Day06.hs similarity index 61% rename from y2019/src/Day6.hs rename to haskellAoC/src/Y2019/Day06.hs index 30bea16..974eeaf 100644 --- a/y2019/src/Day6.hs +++ b/haskellAoC/src/Y2019/Day06.hs @@ -1,4 +1,4 @@ -module Day6 (day6) where +module Y2019.Day06 (day6) where import Data.Maybe import qualified Data.Map as Map @@ -29,23 +29,13 @@ countTuples ((_, ""):xs) = 1 + countTuples xs countTuples ((_, _):xs) = 2 + countTuples xs countTuples [] = 0 -day6 :: IO () -day6 = do - putStrLn "AoC 2019 day 6" - putStr "Input >" - input <- getContents - putStrLn "" - - -- 1 orbits 2 - let orbitsMap = Map.fromList (map (\r -> (r !! 1, r !! 0)) (map (splitOn ")") (lines input))) - let orbitingObjects = Map.keysSet orbitsMap - - let nbOrbitsPerObject = map (orbitLength orbitsMap) (Set.toList orbitingObjects) - - putStrLn $ "Part 1: " ++ (show (sum nbOrbitsPerObject)) - - let myOrbits = reverse (tail (getOrbits orbitsMap "YOU")) - let santaOrbits = reverse (tail (getOrbits orbitsMap "SAN")) - - let elems = dropWhile (\(a, b) -> a == b) (zipWithPadding [] [] myOrbits santaOrbits) - putStrLn $ "Part 2: " ++ (show (countTuples elems)) +day6 :: [String] -> (String, String) +day6 input = (part1, part2) + where orbitsMap = Map.fromList (map (\r -> (r !! 1, r !! 0)) (map (splitOn ")") input)) + orbitingObjects = Map.keysSet orbitsMap + nbOrbitsPerObject = map (orbitLength orbitsMap) (Set.toList orbitingObjects) + part1 = show $ sum nbOrbitsPerObject + myOrbits = reverse $ tail $ getOrbits orbitsMap "YOU" + santaOrbits = reverse $ tail $ getOrbits orbitsMap "SAN" + elems = dropWhile (\(a, b) -> a == b) (zipWithPadding [] [] myOrbits santaOrbits) + part2 = show $ countTuples elems diff --git a/y2019/src/Day7.hs b/haskellAoC/src/Y2019/Day07.hs similarity index 76% rename from y2019/src/Day7.hs rename to haskellAoC/src/Y2019/Day07.hs index f585d9b..b3c639b 100644 --- a/y2019/src/Day7.hs +++ b/haskellAoC/src/Y2019/Day07.hs @@ -1,7 +1,7 @@ -module Day7 (day7) where +module Y2019.Day07 (day7) where import Data.List -import Intcode +import Y2019.Intcode processProgram :: [Int] -> [Int] -> Int processProgram program inputs = head outputs @@ -22,18 +22,12 @@ testCombinationsP2 :: [Int] -> [([Int], Int)] testCombinationsP2 program = map (\p -> (p, runProgramV3 program p)) phasesPerm where phasesPerm = permutations [5..9] -day7 :: IO () -day7 = do - putStrLn $ "AoC 2019 day 7" - input <- getLine - - let program = parseProgram input - let combinationsP1 = testCombinationsP1 program - - let p1 = maximumBy (\(_, a) (_, b) -> compare a b) combinationsP1 - - putStrLn $ "Part 1: " ++ (show p1) - +day7 :: [String] -> (String, String) +day7 (input:_) = (part1, part2) + where program = parseProgram input + combinationsP1 = testCombinationsP1 program + part1 = show $ maximumBy (\(_, a) (_, b) -> compare a b) combinationsP1 + part2 = "" -- WIP -- let combinationsP2 = testCombinationsP2 program -- let p2 = maximumBy (\(_, a) (_, b) -> compare a b) combinationsP2 diff --git a/haskellAoC/src/Y2019/Day08.hs b/haskellAoC/src/Y2019/Day08.hs new file mode 100644 index 0000000..e4c2f60 --- /dev/null +++ b/haskellAoC/src/Y2019/Day08.hs @@ -0,0 +1,37 @@ +module Y2019.Day08 (day8) where + +import Data.List.Split +import Data.List + +width :: Int +width = 25 + +height :: Int +height = 6 + +buildLayers :: String -> Int -> Int -> [[Char]] +buildLayers "" _ _ = [] +buildLayers input w h = front:(buildLayers back w h) + where (front, back) = splitAt (w * h) input + +decodeLayers :: [String] -> String +decodeLayers layers = foldl decodeLayers' (replicate (width * height) '2') layers + where decodeLayers' acc layer = map (\(a, l) -> if a == '2' then l else a) (zip acc layer) + +day8 :: [String] -> (String, String) +day8 (input:_) = (part1, part2) + where layers = buildLayers input width height + countDigit d = length . (filter (== d)) + min0layer = minimumBy (\ a b -> (countDigit '0' a) `compare` (countDigit '0' b)) layers + p1nbOf1 = countDigit '1' min0layer + p1nbOf2 = countDigit '2' min0layer + + part1 = show $ p1nbOf1 * p1nbOf2 + + decoded = unlines (chunksOf width (decodeLayers layers)) + + repl '0' = ' ' + repl '1' = '#' + repl c = c + + part2 = map repl decoded diff --git a/haskellAoC/src/Y2019/Day09.hs b/haskellAoC/src/Y2019/Day09.hs new file mode 100644 index 0000000..ff6bf1a --- /dev/null +++ b/haskellAoC/src/Y2019/Day09.hs @@ -0,0 +1,9 @@ +module Y2019.Day09 (day9) where + +import Y2019.Intcode + +day9 :: [String] -> (String, String) +day9 (input:_) = (part1, part2) + where memory = parseProgram input + part1 = show $ runProgramV2 [1] memory + part2 = show $ runProgramV2 [2] memory diff --git a/y2019/src/Day10.hs b/haskellAoC/src/Y2019/Day10.hs similarity index 70% rename from y2019/src/Day10.hs rename to haskellAoC/src/Y2019/Day10.hs index 00c2c96..b312e01 100644 --- a/y2019/src/Day10.hs +++ b/haskellAoC/src/Y2019/Day10.hs @@ -1,4 +1,4 @@ -module Day10 (day10) where +module Y2019.Day10 (day10) where import Data.List import Geo.Vector @@ -40,22 +40,16 @@ getLaserOrder ((p:[]):xs) = p:(getLaserOrder xs) getLaserOrder ((p:ps):xs) = p:(getLaserOrder (xs ++ [ps])) getLaserOrder [] = [] -day10 :: IO () -day10 = do - putStrLn $ "AoC 2019 day 10" - input <- getContents - let asteroids = parseInput 0 $ lines input - - let part1 = maximumBy (\(_, a) (_, b) -> compare a b) $ map countFn asteroids - where countFn pt = (pt, (length $ nub $ getDirVectors pt asteroids) - 1) - - putStrLn $ "Part 1: " ++ (show $ part1) - - let p2 = getLaserOrder $ - map (\m -> map (\(p, _, _) -> p) m) $ - groupBy (\(_, v1, _) (_, v2, _) -> v1 == v2) $ - sortBy asteroidSorting $ - getVectorAndDistPerPoint asteroids $ - fst part1 - - putStrLn $ "Part 2: " ++ (show $ p2 !! 200) +day10 :: [String] -> (String, String) +day10 input = (part1, part2) + where asteroids = parseInput 0 input + p1 = maximumBy (\(_, a) (_, b) -> compare a b) $ map countFn asteroids + countFn pt = (pt, (length $ nub $ getDirVectors pt asteroids) - 1) + p2 = getLaserOrder $ + map (\m -> map (\(p, _, _) -> p) m) $ + groupBy (\(_, v1, _) (_, v2, _) -> v1 == v2) $ + sortBy asteroidSorting $ + getVectorAndDistPerPoint asteroids $ + fst p1 + part1 = show $ p1 + part2 = show $ p2 !! 200 diff --git a/y2019/src/Day11.hs b/haskellAoC/src/Y2019/Day11.hs similarity index 75% rename from y2019/src/Day11.hs rename to haskellAoC/src/Y2019/Day11.hs index 0998ddf..fe2676a 100644 --- a/y2019/src/Day11.hs +++ b/haskellAoC/src/Y2019/Day11.hs @@ -1,8 +1,8 @@ -module Day11 (day11) where +module Y2019.Day11 (day11) where import qualified Data.Map as M import Data.List -import Intcode +import Y2019.Intcode getCoords :: ([Int] -> Int) -> [((Int, Int), Int)] -> (Int, Int) getCoords fn (((x, y),_):xs) = getCoords' x y xs @@ -24,15 +24,10 @@ draw painting = draw' minCoords maxCoords (snd minCoords) | otherwise = (drawLine curY (minX, maxX) minX painting) ++ (draw' minCoords maxCoords (curY + 1)) -day11 :: IO () -day11 = do - putStrLn "AoC 2019 day 11" - input <- getLine - let memory = parseProgram input - let painting = runProgramPaint memory 0 - let registration = runProgramPaint memory 1 - - putStrLn $ "Part 1: " ++ (show $ length $ painting) - - putStrLn $ "Part 2:" - putStrLn $ draw registration +day11 :: [String] -> (String, String) +day11 (input:_) = (part1, part2) + where memory = parseProgram input + painting = runProgramPaint memory 0 + registration = runProgramPaint memory 1 + part1 = show $ length $ painting + part2 = draw registration diff --git a/y2019/src/Day12.hs b/haskellAoC/src/Y2019/Day12.hs similarity index 77% rename from y2019/src/Day12.hs rename to haskellAoC/src/Y2019/Day12.hs index 58becb8..06810c3 100644 --- a/y2019/src/Day12.hs +++ b/haskellAoC/src/Y2019/Day12.hs @@ -1,4 +1,4 @@ -module Day12 (day12) where +module Y2019.Day12 (day12) where import Data.List import Data.List.Split @@ -44,18 +44,14 @@ moonEnergy (Moon (V px py pz) (V vx vy vz)) = potentialEnergy * kineticEnergy where potentialEnergy = (abs px) + (abs py) + (abs pz) kineticEnergy = (abs vx) + (abs vy) + (abs vz) -day12 :: IO () -day12 = do - putStrLn "AoC 2019 day 12" +day12 :: [String] -> (String, String) +day12 input = (part1, part2) + where planets = map parseLine $ filter (not . null) input + iteration = iterate computeStep planets - input <- getContents + at1000 = iteration !! 1000 + part1 = show $ sum $ map moonEnergy $ at1000 - let planets = map parseLine $ filter (not . null) $ splitOn "\n" input - let iteration = iterate computeStep planets - - let at1000 = iteration !! 1000 - putStrLn $ "Part 1: " ++ (show $ sum $ map moonEnergy $ at1000) - - -- ok, inefficient, need something better - let idx = elemIndex planets $ tail iteration - putStrLn $ "Part 2: " ++ (show $ fmap (+1) idx) + -- ok, inefficient, need something better + idx = elemIndex planets $ tail iteration + part2 = show $ fmap (+1) idx diff --git a/haskellAoC/src/Y2019/Day13.hs b/haskellAoC/src/Y2019/Day13.hs new file mode 100644 index 0000000..f179108 --- /dev/null +++ b/haskellAoC/src/Y2019/Day13.hs @@ -0,0 +1,19 @@ +module Y2019.Day13 (day13) where + +import Y2019.Intcode + +parseOutput :: [Int] -> [(Int, Int, Int)] +parseOutput (x:(y:(t:xs))) = (x, y, t):(parseOutput xs) +parseOutput _ = [] + +day13 :: [String] -> (String, String) +day13 (input:_) = (part1, part2) + where memory = parseProgram input + outputP1 = parseOutput $ runProgramV2 [] memory + part1 = show $ length $ filter (\(_,_,t) -> t == 2) outputP1 + part2 = "WIP" + + -- let hackedMemory = 2:xs + -- where (_:xs) = memory + + -- let outputP2 = parseOutput $ runProgramV2 [] hackedMemory diff --git a/haskellAoC/src/Y2019/Days.hs b/haskellAoC/src/Y2019/Days.hs new file mode 100644 index 0000000..0117ec4 --- /dev/null +++ b/haskellAoC/src/Y2019/Days.hs @@ -0,0 +1,32 @@ +module Y2019.Days (y19day01, y19day02, y19day03, y19day04, y19day05, y19day06, + y19day07, y19day08, y19day09, y19day10, y19day11, y19day12, + y19day13 + ) where + +import Y2019.Day01 +import Y2019.Day02 +import Y2019.Day03 +import Y2019.Day04 +import Y2019.Day05 +import Y2019.Day06 +import Y2019.Day07 +import Y2019.Day08 +import Y2019.Day09 +import Y2019.Day10 +import Y2019.Day11 +import Y2019.Day12 +import Y2019.Day13 + +y19day01 = day1 +y19day02 = day2 +y19day03 = day3 +y19day04 = day4 +y19day05 = day5 +y19day06 = day6 +y19day07 = day7 +y19day08 = day8 +y19day09 = day9 +y19day10 = day10 +y19day11 = day11 +y19day12 = day12 +y19day13 = day13 diff --git a/y2019/src/Intcode.hs b/haskellAoC/src/Y2019/Intcode.hs similarity index 98% rename from y2019/src/Intcode.hs rename to haskellAoC/src/Y2019/Intcode.hs index 400c25e..39024be 100644 --- a/y2019/src/Intcode.hs +++ b/haskellAoC/src/Y2019/Intcode.hs @@ -1,4 +1,4 @@ -module Intcode (parseProgram, runProgramV1, runProgramV2, runProgramV3, runProgramPaint) where +module Y2019.Intcode (parseProgram, runProgramV1, runProgramV2, runProgramV3, runProgramPaint) where import Data.Map import Data.List.Split diff --git a/y2020/src/Day01.hs b/haskellAoC/src/Y2020/Day01.hs similarity index 65% rename from y2020/src/Day01.hs rename to haskellAoC/src/Y2020/Day01.hs index 7c7e335..b019260 100644 --- a/y2020/src/Day01.hs +++ b/haskellAoC/src/Y2020/Day01.hs @@ -1,9 +1,7 @@ -module Day01 (day01) where +module Y2020.Day01 (y20day01) where import Data.Maybe import Data.Sort -import Debug.Trace - findPair :: Int -> Int -> [Int] -> Maybe (Int, Int) findPair target x (h:t) @@ -25,14 +23,11 @@ findFirstMatchingTriplet target (x:xs) | otherwise = findFirstMatchingTriplet target xs where res = findFirstMatchingPair (target - x) xs -day01 :: IO () -day01 = do - putStrLn "AoC 2020 day 1" - input <- getContents - let entries = (sort (map read (lines input))) :: [Int] - - let Just (a, b) = findFirstMatchingPair 2020 entries - putStrLn $ "Part 1: " ++ (show (a * b)) - - let (x, y, z) = findFirstMatchingTriplet 2020 entries - putStrLn $ "Part 2: " ++ (show (x * y * z)) +y20day01 :: [String] -> (String, String) +y20day01 input = (part1, part2) + where + entries = (sort (map read input)) :: [Int] + Just (a, b) = findFirstMatchingPair 2020 entries + (x, y, z) = findFirstMatchingTriplet 2020 entries + part1 = show (a * b) + part2 = show (x * y * z) diff --git a/haskellAoC/src/Y2020/Day02.hs b/haskellAoC/src/Y2020/Day02.hs new file mode 100644 index 0000000..68ea654 --- /dev/null +++ b/haskellAoC/src/Y2020/Day02.hs @@ -0,0 +1,25 @@ +module Y2020.Day02 (y20day02) where + +import Data.List.Split + +parseInput :: String -> (Int, Int, Char, String) +parseInput input = (qty 0, qty 1, (parts !! 1) !! 0, parts !! 2) + where parts = splitOn " " $ filter (\c -> not $ elem c ":") input + qty n = read $ (!! n) $ splitOn "-" $ (parts !! 0) + +isValidPassP1 :: (Int, Int, Char, String) -> Bool +isValidPassP1 (minP, maxP, c, pass) = count >= minP && count <= maxP + where count = length $ filter (== c) pass + +isValidPassP2 :: (Int, Int, Char, String) -> Bool +isValidPassP2 (pos1, pos2, c, pass) = isPos pos1 `xor` isPos pos2 + where isPos p = (pass !! (p - 1)) == c + xor a b = (a || b) && (a /= b) + +y20day02 :: [String] -> (String, String) +y20day02 input = (part1, part2) + where + entries = map parseInput $ input + strCount f xs = show $ length $ filter f xs + part1 = strCount isValidPassP1 entries + part2 = strCount isValidPassP2 entries diff --git a/haskellAoC/src/Y2020/Day03.hs b/haskellAoC/src/Y2020/Day03.hs new file mode 100644 index 0000000..33e0ca8 --- /dev/null +++ b/haskellAoC/src/Y2020/Day03.hs @@ -0,0 +1,22 @@ +module Y2020.Day03 (y20day03) where + +walkMap :: (Int, Int) -> (Int, Int) -> [(Int, Int)] +walkMap (w, h) (wstep, hstep) = zip wCoords hCoords + where wCoords = map (`mod` w) $ take h $ iterate (+ wstep) 0 + hCoords = take h $ iterate (+ hstep) 0 + +getCharAtPos :: [String] -> (Int, Int) -> Char +getCharAtPos myMap (w, h) + | h <= length myMap = (myMap !! h) !! w + | otherwise = '\0' + +getNumberOfTrees :: [String] -> [(Int, Int)] -> Int +getNumberOfTrees myMap coords = length $ filter (== '#') $ map (getCharAtPos myMap) coords + +y20day03 :: [String] -> (String, String) +y20day03 input = (part1, part2) + where width = length $ input !! 0 + height = (length $ input) + getNb slope = getNumberOfTrees input $ walkMap (width, height) slope + part1 = show $ getNb (3, 1) + part2 = show $ product $ map getNb [(1, 1), (3, 1), (5, 1), (7, 1), (1, 2)] diff --git a/haskellAoC/src/Y2020/Days.hs b/haskellAoC/src/Y2020/Days.hs new file mode 100644 index 0000000..167c268 --- /dev/null +++ b/haskellAoC/src/Y2020/Days.hs @@ -0,0 +1,5 @@ +module Y2020.Days (y20day01, y20day02, y20day03) where + +import Y2020.Day01 +import Y2020.Day02 +import Y2020.Day03 diff --git a/y2019/stack.yaml b/haskellAoC/stack.yaml similarity index 99% rename from y2019/stack.yaml rename to haskellAoC/stack.yaml index dbba8d7..1983f0d 100644 --- a/y2019/stack.yaml +++ b/haskellAoC/stack.yaml @@ -17,7 +17,7 @@ # # resolver: ./custom-snapshot.yaml # resolver: https://example.com/snapshots/2018-01-01.yaml -resolver: lts-14.16 +resolver: lts-16.24 # User packages to be built. # Various formats can be used as shown in the example below. diff --git a/y2019/stack.yaml.lock b/haskellAoC/stack.yaml.lock similarity index 65% rename from y2019/stack.yaml.lock rename to haskellAoC/stack.yaml.lock index 5e17e80..98c77e4 100644 --- a/y2019/stack.yaml.lock +++ b/haskellAoC/stack.yaml.lock @@ -6,7 +6,7 @@ packages: [] snapshots: - completed: - size: 524804 - url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/14/16.yaml - sha256: 4d1519a4372d051d47a5eae2241cf3fb54e113d7475f89707ddb6ec06add2888 - original: lts-14.16 + size: 532835 + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/24.yaml + sha256: cf2b52420b2262fe9cf0f6744929120131abd6675b1c3fb2d8b155a47f80d103 + original: lts-16.24 diff --git a/y2019/test/Spec.hs b/haskellAoC/test/Spec.hs similarity index 100% rename from y2019/test/Spec.hs rename to haskellAoC/test/Spec.hs diff --git a/y2019/.gitignore b/y2019/.gitignore deleted file mode 100644 index 8a2c0bb..0000000 --- a/y2019/.gitignore +++ /dev/null @@ -1,3 +0,0 @@ -.stack-work/ -y2019.cabal -*~ \ No newline at end of file diff --git a/y2019/ChangeLog.md b/y2019/ChangeLog.md deleted file mode 100644 index 5c39b4e..0000000 --- a/y2019/ChangeLog.md +++ /dev/null @@ -1,3 +0,0 @@ -# Changelog for y2019 - -## Unreleased changes diff --git a/y2019/LICENSE b/y2019/LICENSE deleted file mode 100644 index e095992..0000000 --- a/y2019/LICENSE +++ /dev/null @@ -1,30 +0,0 @@ -Copyright Xavier Morel (c) 2019 - -All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are met: - - * Redistributions of source code must retain the above copyright - notice, this list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above - copyright notice, this list of conditions and the following - disclaimer in the documentation and/or other materials provided - with the distribution. - - * Neither the name of Xavier Morel nor the names of other - contributors may be used to endorse or promote products derived - from this software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. diff --git a/y2019/README.md b/y2019/README.md deleted file mode 100644 index a4f674f..0000000 --- a/y2019/README.md +++ /dev/null @@ -1,4 +0,0 @@ -# Advent of Code 2019 -https://adventofcode.com/2019 - -A good occasion to try Haskell. diff --git a/y2019/package.yaml b/y2019/package.yaml deleted file mode 100644 index 7ebc73f..0000000 --- a/y2019/package.yaml +++ /dev/null @@ -1,50 +0,0 @@ -name: y2019 -version: 0.1.0.0 -github: "mx42/y2019" -license: BSD3 -author: "Xavier Morel" -maintainer: "morelx42@gmail.com" -copyright: "2019 Xavier Morel" - -extra-source-files: -- README.md -- ChangeLog.md - -# Metadata used when publishing your package -# synopsis: Short description of your package -# category: Web - -# To avoid duplicated efforts in documentation and dealing with the -# complications of embedding Haddock markup inside cabal files, it is -# common to point users to the README.md file. -description: Please see the README on GitHub at - -dependencies: -- base >= 4.7 && < 5 -- split -- containers - -library: - source-dirs: src - -executables: - y2019-exe: - main: Main.hs - source-dirs: app - ghc-options: - - -threaded - - -rtsopts - - -with-rtsopts=-N - dependencies: - - y2019 - -tests: - y2019-test: - main: Spec.hs - source-dirs: test - ghc-options: - - -threaded - - -rtsopts - - -with-rtsopts=-N - dependencies: - - y2019 diff --git a/y2019/src/Day1.hs b/y2019/src/Day1.hs deleted file mode 100644 index 03e9374..0000000 --- a/y2019/src/Day1.hs +++ /dev/null @@ -1,24 +0,0 @@ -module Day1 - ( day1 - ) where - -massFuelReq :: Integer -> Integer -massFuelReq mass = (floor (fromIntegral mass / 3)) - 2 - -moduleFuelReq :: Integer -> Integer -moduleFuelReq mass - | req > 0 = req + moduleFuelReq req - | req <= 0 = 0 - where req = massFuelReq mass - -day1 :: IO () -day1 = do - putStrLn "AoC 2019 day 1" - putStr "Enter input >" - input <- getContents - putStrLn "" - let modules = (map read (lines input)) - putStrLn "Part 1" - print (sum (map massFuelReq modules)) - putStrLn "Part 2" - print (sum (map moduleFuelReq modules)) diff --git a/y2019/src/Day13.hs b/y2019/src/Day13.hs deleted file mode 100644 index 1dff4e6..0000000 --- a/y2019/src/Day13.hs +++ /dev/null @@ -1,22 +0,0 @@ -module Day13 (day13) where - -import Intcode - -parseOutput :: [Int] -> [(Int, Int, Int)] -parseOutput (x:(y:(t:xs))) = (x, y, t):(parseOutput xs) -parseOutput _ = [] - -day13 :: IO () -day13 = do - putStrLn $ "AoC 2019 day 13" - input <- getLine - let memory = parseProgram input - - let outputP1 = parseOutput $ runProgramV2 [] memory - - putStrLn $ "Part1: " ++ (show $ length $ filter (\(_,_,t) -> t == 2) outputP1) - - -- let hackedMemory = 2:xs - -- where (_:xs) = memory - - -- let outputP2 = parseOutput $ runProgramV2 [] hackedMemory diff --git a/y2019/src/Day14.hs b/y2019/src/Day14.hs deleted file mode 100644 index eec0ada..0000000 --- a/y2019/src/Day14.hs +++ /dev/null @@ -1,5 +0,0 @@ -module Day14 (day14) where - -day14 :: IO () -day14 = do - putStrLn "AoC 2019 day 14" diff --git a/y2019/src/Day4.hs b/y2019/src/Day4.hs deleted file mode 100644 index 9734586..0000000 --- a/y2019/src/Day4.hs +++ /dev/null @@ -1,32 +0,0 @@ -module Day4 (day4) where - -import Data.List.Split -import Data.List - -isValid :: (Int -> Bool) -> Int -> Bool -isValid groupsCriteria n = length6 && isSorted && hasGroups - where digits = show n - length6 = (length digits) == 6 - isSorted = digits == sort digits - hasGroups = any (\d -> groupsCriteria (length d)) (group digits) - -getNext :: (Int -> Bool) -> Int -> Int -getNext groupsCriteria cur - | isValid groupsCriteria (cur + 1) = (cur + 1) - | otherwise = getNext groupsCriteria (cur + 1) - -day4 :: IO () -day4 = do - putStrLn "AoC 2019 day 4" - putStr "Enter input >" - input <- getLine - putStrLn "" - - let range = (map read (splitOn "-" input)) :: [Int] - putStrLn ("Range is " ++ show (range !! 0) ++ " to " ++ show (range !! 1)) - - let iterP1 = takeWhile (< (range !! 1)) (iterate (getNext (> 1)) (range !! 0)) - putStrLn ("Part1: " ++ show ((length iterP1) - 1)) - - let iterP2 = takeWhile (< (range !! 1)) (iterate (getNext (== 2)) (range !! 0)) - putStrLn ("Part2: " ++ show ((length iterP2) - 1)) diff --git a/y2019/src/Day5.hs b/y2019/src/Day5.hs deleted file mode 100644 index 70ef52c..0000000 --- a/y2019/src/Day5.hs +++ /dev/null @@ -1,18 +0,0 @@ -module Day5 (day5) where - -import Intcode - -day5 :: IO () -day5 = do - putStrLn "AoC 2019 day 5" - putStr "Input >" - input <- getLine - putStrLn "" - - let intCodes = parseProgram input - - let outputP1 = runProgramV2 [1] intCodes - putStrLn ("Part1: " ++ show (outputP1 !! 0)) - - let outputP2 = runProgramV2 [5] intCodes - putStrLn ("Part2: " ++ show (outputP2 !! 0)) diff --git a/y2019/src/Day8.hs b/y2019/src/Day8.hs deleted file mode 100644 index 36368d5..0000000 --- a/y2019/src/Day8.hs +++ /dev/null @@ -1,44 +0,0 @@ -module Day8 (day8) where - -import Data.List.Split -import Data.List - -width :: Int -width = 25 - -height :: Int -height = 6 - -buildLayers :: String -> Int -> Int -> [[Char]] -buildLayers "" _ _ = [] -buildLayers input w h = front:(buildLayers back w h) - where (front, back) = splitAt (w * h) input - -decodeLayers :: [String] -> String -decodeLayers layers = foldl decodeLayers' (replicate (width * height) '2') layers - where decodeLayers' acc layer = map (\(a, l) -> if a == '2' then l else a) (zip acc layer) - -day8 :: IO () -day8 = do - putStrLn $ "AoC 2019 day 8" - input <- getLine - - let layers = buildLayers input width height - - let countDigit d = length . (filter (== d)) - - let min0layer = minimumBy (\ a b -> (countDigit '0' a) `compare` (countDigit '0' b)) layers - - let p1nbOf1 = countDigit '1' min0layer - let p1nbOf2 = countDigit '2' min0layer - - putStrLn $ "Part 1: " ++ (show (p1nbOf1 * p1nbOf2)) - - putStrLn "Part 2:" - - let decoded = unlines (chunksOf width (decodeLayers layers)) - - let repl '0' = ' ' - repl '1' = '#' - repl c = c - in putStrLn $ map repl decoded diff --git a/y2019/src/Day9.hs b/y2019/src/Day9.hs deleted file mode 100644 index 46e9c1c..0000000 --- a/y2019/src/Day9.hs +++ /dev/null @@ -1,15 +0,0 @@ -module Day9 (day9) where - -import Intcode - -day9 :: IO () -day9 = do - putStrLn $ "AoC 2019 day 9" - input <- getLine - let memory = parseProgram input - - let outputP1 = runProgramV2 [1] memory - putStrLn $ "Part1: " ++ show outputP1 - - let outputP2 = runProgramV2 [2] memory - putStrLn $ "Part2: " ++ show outputP2 diff --git a/y2019/src/DayPicker.hs b/y2019/src/DayPicker.hs deleted file mode 100644 index 64e3192..0000000 --- a/y2019/src/DayPicker.hs +++ /dev/null @@ -1,45 +0,0 @@ -module DayPicker - ( dayPicker - ) -where - -import System.Environment - -import Day1 -import Day2 -import Day3 -import Day4 -import Day5 -import Day6 -import Day7 -import Day8 -import Day9 -import Day10 -import Day11 -import Day12 -import Day13 -import Day14 - --- TODO Better way? -load :: [String] -> IO () -load [] = putStrLn "Usage: script [day]" -load ("1":_) = day1 -load ("2":_) = day2 -load ("3":_) = day3 -load ("4":_) = day4 -load ("5":_) = day5 -load ("6":_) = day6 -load ("7":_) = day7 -load ("8":_) = day8 -load ("9":_) = day9 -load ("10":_) = day10 -load ("11":_) = day11 -load ("12":_) = day12 -load ("13":_) = day13 -load ("14":_) = day14 -load _ = putStrLn "Unavailable date" - -dayPicker :: IO () -dayPicker = do - args <- getArgs - load args diff --git a/y2020/ChangeLog.md b/y2020/ChangeLog.md deleted file mode 100644 index b2b7b2a..0000000 --- a/y2020/ChangeLog.md +++ /dev/null @@ -1,3 +0,0 @@ -# Changelog for y2020 - -## Unreleased changes diff --git a/y2020/README.md b/y2020/README.md deleted file mode 100644 index 94448b0..0000000 --- a/y2020/README.md +++ /dev/null @@ -1,4 +0,0 @@ -# Advent of Code 2020 -https://adventofcode.com/2020 - -A good occasion to try Haskell. diff --git a/y2020/Setup.hs b/y2020/Setup.hs deleted file mode 100644 index 9a994af..0000000 --- a/y2020/Setup.hs +++ /dev/null @@ -1,2 +0,0 @@ -import Distribution.Simple -main = defaultMain diff --git a/y2020/app/Main.hs b/y2020/app/Main.hs deleted file mode 100644 index d7565bd..0000000 --- a/y2020/app/Main.hs +++ /dev/null @@ -1,6 +0,0 @@ -module Main where - -import DayPicker - -main :: IO () -main = dayPicker diff --git a/y2020/src/DayPicker.hs b/y2020/src/DayPicker.hs deleted file mode 100644 index 84111b4..0000000 --- a/y2020/src/DayPicker.hs +++ /dev/null @@ -1,19 +0,0 @@ -module DayPicker - ( dayPicker - ) -where - -import System.Environment - -import Day01 - --- TODO Better way? -load :: [String] -> IO () -load [] = putStrLn "Usage: script [day]" -load ("01":_) = day01 -load _ = putStrLn "Unavailable date" - -dayPicker :: IO () -dayPicker = do - args <- getArgs - load args diff --git a/y2020/src/Geo/Point.hs b/y2020/src/Geo/Point.hs deleted file mode 100644 index c7650b8..0000000 --- a/y2020/src/Geo/Point.hs +++ /dev/null @@ -1,24 +0,0 @@ -module Geo.Point - ( Point(..), - origin, - manhattanDist, - add, - sub - ) where - -data Point = Point { x :: Double, y :: Double } deriving (Show, Eq) - --- instance Eq Point where --- (==) (Point x1 y1) (Point x2 y2) = x1 == x2 && y1 == y2 - -origin :: Point -origin = Point 0 0 - -manhattanDist :: Point -> Point -> Double -manhattanDist a b = abs(x(b) - x(a)) + abs(y(b) - y(a)) - -add :: Point -> Point -> Point -add (Point xa ya) (Point xb yb) = Point (xa + xb) (ya + yb) - -sub :: Point -> Point -> Point -sub (Point xa ya) (Point xb yb) = Point (xa - xb) (ya - yb) diff --git a/y2020/src/Geo/Segment.hs b/y2020/src/Geo/Segment.hs deleted file mode 100644 index d5bc35d..0000000 --- a/y2020/src/Geo/Segment.hs +++ /dev/null @@ -1,52 +0,0 @@ -module Geo.Segment - ( Segment(..), - directionalVect, - segmentIntersection, - linkVectors, - linkPoints, - onSegment - ) where - -import Geo.Point -import Geo.Vector - -data Segment = Segment { src :: Point, dst :: Point } deriving (Show) - -directionalVect :: Segment -> Vector -directionalVect (Segment s d) = directionalVectorFromPoint (d `sub` s) - -onSegment :: Point -> Segment -> Bool -onSegment p@(Point px py) (Segment s@(Point sx sy) d@(Point dx dy)) - | p == d = True - | p == s = True - | sx == dx && sx == px && (between py sy dy) = True - | sy == dy && sy == py && (between px sx dx) = True - | otherwise = False - where between p' s' d' = if s' < d' then p' >= s' && p' <= d' else p' >= d' && p' <= s' - -segmentIntersection :: Segment -> Segment -> Maybe Point -segmentIntersection s1 s2 = - if t1 < 0 || t1 > 1 || t2 < 0 || t2 > 1 - then Nothing - else Just (directionalVectorToPoint (Vector t1 t2) (src(s1))) - where dirS1 = directionalVect s1 - dirS2 = directionalVect s2 - determinant = determinantVector dirS1 dirS2 - dirX = directionalVectorFromPoint (src(s2) `sub` src(s1)) - t1 = (determinantVector dirX dirS2) / determinant - t2 = (determinantVector dirX dirS1) / determinant - -linkPoints :: [Point] -> [Segment] -linkPoints pts = foldl addPointToSegments [] pts - -linkVectors :: [Vector] -> [Segment] -linkVectors vectors = linkPoints (reverse points) - where points = foldl linkVectors' [] vectors - -linkVectors' :: [Point] -> Vector -> [Point] -linkVectors' [] v = [addV2P origin v] -linkVectors' xs@(p:_) v = (addV2P p v):xs - -addPointToSegments :: [Segment] -> Point -> [Segment] -addPointToSegments [] pt = [Segment origin pt] -addPointToSegments xs@(h:_) pt = (Segment (dst(h)) pt):xs diff --git a/y2020/src/Geo/Vector.hs b/y2020/src/Geo/Vector.hs deleted file mode 100644 index 5d8b2e3..0000000 --- a/y2020/src/Geo/Vector.hs +++ /dev/null @@ -1,43 +0,0 @@ -module Geo.Vector - ( Vector(..), - determinantVector, - directionalVectorFromPoint, - directionalVectorToPoint, - nilVector, - addV2P, - roundVecAtN, - roundN, - vec2angle - ) where - -import Geo.Point - -data Vector = Vector { x :: Double, y :: Double } deriving (Show, Eq) - -addV2P :: Point -> Vector -> Point -addV2P (Point xp yp) (Vector xv yv) = Point (xp + xv) (yp + yv) - -nilVector :: Vector -nilVector = Vector 0 0 - -roundVecAtN :: Int -> Vector -> Vector -roundVecAtN prec (Vector vx vy) = Vector (roundN prec vx) (roundN prec vy) - --- https://stackoverflow.com/questions/12450501/round-number-to-specified-number-of-digits -roundN :: Int -> Double -> Double -roundN prec val = (fromInteger $ round $ val * (10 ^ prec)) / (10.0 ^^ prec) - -directionalVectorFromPoint :: Point -> Vector -directionalVectorFromPoint (Point px py) = Vector (px / len) (py / len) - where len = sqrt(px * px + py * py) - -determinantVector :: Vector -> Vector -> Double -determinantVector (Vector x1 y1) (Vector x2 y2) = (x1 * y2) - (y1 * x2) - -directionalVectorToPoint :: Vector -> Point -> Point -directionalVectorToPoint (Vector vx vy) (Point px py) = Point (vx * px) (vy * py) - -vec2angle :: Vector -> Double -vec2angle (Vector vx vy) = roundN 5 angle' - where angle = atan2 vx vy - angle' = pi - angle diff --git a/y2020/stack.yaml b/y2020/stack.yaml deleted file mode 100644 index dbba8d7..0000000 --- a/y2020/stack.yaml +++ /dev/null @@ -1,66 +0,0 @@ -# This file was automatically generated by 'stack init' -# -# Some commonly used options have been documented as comments in this file. -# For advanced use and comprehensive documentation of the format, please see: -# https://docs.haskellstack.org/en/stable/yaml_configuration/ - -# Resolver to choose a 'specific' stackage snapshot or a compiler version. -# A snapshot resolver dictates the compiler version and the set of packages -# to be used for project dependencies. For example: -# -# resolver: lts-3.5 -# resolver: nightly-2015-09-21 -# resolver: ghc-7.10.2 -# -# The location of a snapshot can be provided as a file or url. Stack assumes -# a snapshot provided as a file might change, whereas a url resource does not. -# -# resolver: ./custom-snapshot.yaml -# resolver: https://example.com/snapshots/2018-01-01.yaml -resolver: lts-14.16 - -# User packages to be built. -# Various formats can be used as shown in the example below. -# -# packages: -# - some-directory -# - https://example.com/foo/bar/baz-0.0.2.tar.gz -# subdirs: -# - auto-update -# - wai -packages: -- . -# Dependency packages to be pulled from upstream that are not in the resolver. -# These entries can reference officially published versions as well as -# forks / in-progress versions pinned to a git hash. For example: -# -# extra-deps: -# - acme-missiles-0.3 -# - git: https://github.com/commercialhaskell/stack.git -# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a -# -# extra-deps: [] - -# Override default flag values for local packages and extra-deps -# flags: {} - -# Extra package databases containing global packages -# extra-package-dbs: [] - -# Control whether we use the GHC we find on the path -# system-ghc: true -# -# Require a specific version of stack, using version ranges -# require-stack-version: -any # Default -# require-stack-version: ">=2.1" -# -# Override the architecture used by stack, especially useful on Windows -# arch: i386 -# arch: x86_64 -# -# Extra directories used by stack for building -# extra-include-dirs: [/path/to/dir] -# extra-lib-dirs: [/path/to/dir] -# -# Allow a newer minor version of GHC than the snapshot specifies -# compiler-check: newer-minor diff --git a/y2020/stack.yaml.lock b/y2020/stack.yaml.lock deleted file mode 100644 index 5e17e80..0000000 --- a/y2020/stack.yaml.lock +++ /dev/null @@ -1,12 +0,0 @@ -# This file was autogenerated by Stack. -# You should not edit this file by hand. -# For more information, please see the documentation at: -# https://docs.haskellstack.org/en/stable/lock_files - -packages: [] -snapshots: -- completed: - size: 524804 - url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/14/16.yaml - sha256: 4d1519a4372d051d47a5eae2241cf3fb54e113d7475f89707ddb6ec06add2888 - original: lts-14.16 diff --git a/y2020/test/Spec.hs b/y2020/test/Spec.hs deleted file mode 100644 index cd4753f..0000000 --- a/y2020/test/Spec.hs +++ /dev/null @@ -1,2 +0,0 @@ -main :: IO () -main = putStrLn "Test suite not yet implemented"