setup cabal

This commit is contained in:
qvalentin 2022-12-17 14:50:06 +01:00
parent b4ad4cffd8
commit 09cab9fc54
13 changed files with 1395 additions and 0 deletions

35
advent-of-code.cabal Normal file
View File

@ -0,0 +1,35 @@
cabal-version: 2.4
name: advent-of-code
version: 0.1.0.0
-- A short (one-line) description of the package.
-- synopsis:
-- A longer description of the package.
-- description:
-- A URL where users can report bugs.
-- bug-reports:
-- The license under which the package is released.
-- license:
author: qvalentin
maintainer: valentin.theodor@web.de
-- A copyright notice.
-- copyright:
-- category:
extra-source-files: CHANGELOG.md
executable one
main-is: one.hs
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
build-depends: base ^>=4.14.3.0
hs-source-dirs: app
default-language: Haskell2010
ghc-options: -dynamic -O2

4
app/Main.hs Normal file
View File

@ -0,0 +1,4 @@
module Main where
main :: IO ()
main = putStrLn "Hello, Haskell!"

31
app/four-easy.hs Normal file
View File

@ -0,0 +1,31 @@
import Control.Monad
import Data.Char
parseLine :: String -> [[Int]]
parseLine line = [parseAssignment $ takeWhile (/= ',') line,
parseAssignment $ drop 1 $ dropWhile (',' /= ) line]
parseAssignment :: String -> [Int]
parseAssignment assignment = do
let first = takeWhile ('-' /=) assignment
let second = drop 1 $ dropWhile ('-' /=) assignment
[(read first).. (read second)]
isIncludedElseWhere :: [[Int]] -> [Int] -> [[Int]] -> Int -> Int
isIncludedElseWhere previous current [] count=count
isIncludedElseWhere previous current next count=do
let found = (isIncluded current previous && isIncluded current next)
(if found then 1 else 0) +
(isIncludedElseWhere (current:previous) (head next) (tail next) count)
isIncluded :: [Int] -> [[Int]] -> Bool
isIncluded current list = any includes list
where
includes :: [Int] -> Bool
includes range' = all (`elem` range') current
main = do
input <- readFile "four-input2.txt"
let lists= ( join $ map (parseLine) $ lines input)
print $ isIncludedElseWhere [] (head lists) (tail lists) 0

28
app/four.hs Normal file
View File

@ -0,0 +1,28 @@
import Control.Monad
import Data.Char
parseLine :: String -> [[Int]]
parseLine line = [parseAssignment $ takeWhile (/= ',') line,
parseAssignment $ drop 1 $ dropWhile (',' /= ) line]
parseAssignment :: String -> [Int]
parseAssignment assignment = do
let first = takeWhile ('-' /=) assignment
let second = drop 1 $ dropWhile ('-' /=) assignment
[(read first).. (read second)]
isIncluded :: [Int] -> [[Int]] -> Bool
isIncluded current list = any includes list
where
includes :: [Int] -> Bool
includes range' = all (`elem` range') current
coveredByPartner :: [[Int]] -> Bool
coveredByPartner [first,second] = isIncluded first [second] || isIncluded second [first]
main = do
input <- readFile "four-input.txt"
let lists= (map (parseLine) $ lines input)
print $ length $ filter id $ map coveredByPartner lists

25
app/four2.hs Normal file
View File

@ -0,0 +1,25 @@
import Control.Monad
import Data.Char
import Data.List
parseLine :: String -> [[Int]]
parseLine line = [parseAssignment $ takeWhile (/= ',') line,
parseAssignment $ drop 1 $ dropWhile (',' /= ) line]
parseAssignment :: String -> [Int]
parseAssignment assignment = do
let first = takeWhile ('-' /=) assignment
let second = drop 1 $ dropWhile ('-' /=) assignment
[(read first).. (read second)]
coveredByPartner :: [[Int]] -> Bool
coveredByPartner [first,second] = 0 /= (length $ intersect first second)
main = do
input <- readFile "four-input.txt"
let lists= (map (parseLine) $ lines input)
print $ length $ filter id $ map coveredByPartner lists

14
app/one.hs Normal file
View File

@ -0,0 +1,14 @@
import Text.Read
f :: (Int,Int) -> Maybe Int -> (Int,Int)
f (max,current) (Just next) = (max,current+next)
f (currentMax,current) (Nothing) = (max currentMax current ,0)
result=fst $ foldl f (0,0) (map (readMaybe) $lines "1000\n2000\n3000\n\n4000\n1000\n\n1000")
compute input=fst $ foldl f (0,0) $ map (readMaybe) $lines input
main = do
content <- readFile "elves.txt"
putStrLn $ show $compute content

12
app/one2.hs Normal file
View File

@ -0,0 +1,12 @@
import Text.Read
import Data.List
f :: ([Int],Int) -> Maybe Int -> ([Int],Int)
f (max,current) (Just next) = (max,current+next)
f (currentMax,current) (Nothing) = (take 3 $ reverse $ sort (current:currentMax) ,0)
compute input=sum $fst $ foldl f ([0],0) $ map (readMaybe) $lines input
main = do
content <- readFile "elves.txt"
putStrLn $ show $compute content

85
app/seven.hs Normal file
View File

@ -0,0 +1,85 @@
-- everything stolen from http://learnyouahaskell.com/zippers#a-very-simple-file-system
import Control.Monad
data FS = FS [Inode]
data Inode = Dir Name [Inode] | File Name Size deriving(Show)
type Name = String
type Size = Int
data Command = Ls | Cd Name | CdUp | CdRoot deriving(Show)
data Line = LineC Command | LineI Inode deriving(Show)
parseCommand :: String -> Command
parseCommand "ls" =Ls
parseCommand "cd .." =CdUp
parseCommand ('c':'d':' ':name) =(Cd name)
parseInode :: String -> Inode
parseInode ('d':'i':'r':' ': name) = Dir name []
parseInode input = File (drop 1 $ dropWhile (/= ' ') input) (read $ takeWhile (/= ' ') input)
parseEither :: String -> Line
parseEither ('$':' ':command) =LineC $ parseCommand command
parseEither input= LineI $ parseInode input
foldFunction :: FSZipper -> Line -> FSZipper
foldFunction zipper (LineC Ls) = zipper
foldFunction zipper (LineC (Cd name)) = fsTo name zipper
foldFunction zipper (LineC CdUp) = fsUp zipper
foldFunction zipper (LineI inode) = fsNewInode inode zipper
data FSCrumb = FSCrumb Name [Inode] [Inode] deriving (Show)
type FSZipper = (Inode,[FSCrumb])
fsUp :: FSZipper -> FSZipper
fsUp (item, FSCrumb name ls rs:bs) = (Dir name (ls ++ [item] ++ rs), bs)
fsUpToRoot :: FSZipper -> FSZipper
fsUpToRoot ((Dir "/" content),bc) = ((Dir "/" content),bc)
fsUpToRoot zipper = fsUp zipper
fsTo :: Name -> FSZipper -> FSZipper
fsTo name (Dir folderName items, bs) =
let (ls, item:rs) = break (nameIs name) items
in (item, FSCrumb folderName ls rs:bs)
nameIs :: Name -> Inode -> Bool
nameIs name (Dir folderName _) = name == folderName
nameIs name (File fileName _) = name == fileName
fsNewInode :: Inode -> FSZipper -> FSZipper
fsNewInode newInode ((Dir name content),bc) = (Dir name (newInode:content),bc)
initZipper :: FSZipper
initZipper = (Dir "/" [],[])
data InodeSize = DirS Size | FileS Size deriving(Show)
getSize (DirS s)= s
getSize (FileS s)=s
flattenToSmallDirs :: Inode -> [InodeSize]
flattenToSmallDirs (Dir _ children) =
let childSizes =join $ map flattenToSmallDirs children
currentSize=(sum $ map getSize $ childSizes) in
(DirS currentSize):(filter isDir childSizes )
flattenToSmallDirs (File _ size) = [FileS size]
filterSmallDirs :: [InodeSize] -> [Size]
filterSmallDirs ((DirS s):rest) = if (s<100000) then s:(filterSmallDirs rest) else filterSmallDirs rest
filterSmallDirs ((FileS s):rest) = filterSmallDirs rest
filterSmallDirs [] = []
isDir (DirS s)=True
isDir (FileS s)=False
main = do
content <- readFile "seven-input.txt"
let statements = map parseEither $ drop 1 $ lines content
let a = foldl foldFunction initZipper statements
print $ sum $ filterSmallDirs $ flattenToSmallDirs $ fst $ fsUpToRoot a

22
app/three.hs Normal file
View File

@ -0,0 +1,22 @@
import Data.Char
splitlist :: [a] -> ([a],[a])
splitlist list = (take n list,drop n list)
where n = (length list) `div` 2
inBoth :: (Eq a) => ([a],[a]) -> [a]
inBoth (first,second) = do
inFirst <- first
if (inFirst `elem` second) then return inFirst else []
toPriority :: Char -> Int
toPriority char = ordNum - (substract ordNum)
where
ordNum = (ord char)
substract n
| n < 97 = 38
| otherwise = 96
main = do
input <- readFile "three-input.txt"
print $sum $ map (toPriority . head . inBoth . splitlist ) $ lines input

22
app/three2.hs Normal file
View File

@ -0,0 +1,22 @@
import Data.Char
import Data.List.Split
inAll :: [String] -> [Char]
inAll [first,second,third] = do
eachChar <- first
if (eachChar `elem` second && eachChar `elem` third) then return eachChar else []
toPriority :: Char -> Int
toPriority char = ordNum - (substract ordNum)
where
ordNum = (ord char)
substract n
| n < 97 = 38
| otherwise = 96
main = do
input <- readFile "three-input.txt"
print $sum $ map (toPriority . head . inAll ) $ chunksOf 3 $ lines input
--print $map ( inAll ) $ chunksOf 3 $ lines input

41
app/two.hs Normal file
View File

@ -0,0 +1,41 @@
data Rock
data Paper
data Scissors
type X = Rock
type Y = Paper
type Z = Scissors
type A = Rock
type B = Paper
type C = Scissors
data Action = X | Y | Z deriving (Show,Read, Eq)
data Enemy = A | B | C deriving (Show,Read, Eq)
data Game = Game Enemy Action deriving (Show,Read)
selectedScore :: Action -> Int
selectedScore X = 1
selectedScore Y = 2
selectedScore Z = 3
resultScore :: Game -> Int
resultScore (Game A X) = 3
resultScore (Game A Y) = 6
resultScore (Game A Z) = 0
resultScore (Game B X) = 0
resultScore (Game B Y) = 3
resultScore (Game B Z) = 6
resultScore (Game C X) = 6
resultScore (Game C Y) = 0
resultScore (Game C Z) = 3
gameScore :: Game -> Int
gameScore (Game enemy action) = (resultScore (Game enemy action)) + selectedScore action
main = do
input <- readFile "input.txt"
putStrLn $ show$ sum $ map (gameScore . read . ("Game "<> )) $ lines input

44
app/two2.hs Normal file
View File

@ -0,0 +1,44 @@
data Rock
data Paper
data Scissors
type X = Rock
type Y = Paper
type Z = Scissors
type A = Rock
type B = Paper
type C = Scissors
data Action = X | Y | Z deriving (Show,Read, Eq)
data Enemy = A | B | C deriving (Show,Read, Eq)
data Game = Game Enemy Action deriving (Show,Read)
selectedScore :: Action -> Int
--selectedScore X = 1
--selectedScore Y = 2
--selectedScore Z = 3
selectedScore X = 0
selectedScore Y = 3
selectedScore Z = 6
resultScore :: Game -> Int
resultScore (Game A X) = 3
resultScore (Game A Y) = 1
resultScore (Game A Z) = 2
resultScore (Game B X) = 1
resultScore (Game B Y) = 2
resultScore (Game B Z) = 3
resultScore (Game C X) = 2
resultScore (Game C Y) = 3
resultScore (Game C Z) = 1
gameScore :: Game -> Int
gameScore (Game enemy action) = (resultScore (Game enemy action)) + selectedScore action
main = do
input <- readFile "input.txt"
putStrLn $ show$ sum $ map (gameScore . read . ("Game "<> )) $ lines input

1032
seven-input.txtreal Normal file

File diff suppressed because it is too large Load Diff