summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTom Smeding <t.j.smeding@uu.nl>2021-12-12 17:22:49 +0100
committerTom Smeding <t.j.smeding@uu.nl>2021-12-12 17:22:49 +0100
commitda515c27ceffe258a57d7eedbdaed6ca11b3a467 (patch)
tree379421b51e3bf9407db97964ac61f7aa491f1afd
parent8d5debe81041eb0aea1f63c60189aa81a40cebde (diff)
10
-rw-r--r--2021/10.hs43
-rw-r--r--2021/10.in102
2 files changed, 145 insertions, 0 deletions
diff --git a/2021/10.hs b/2021/10.hs
new file mode 100644
index 0000000..ab90d88
--- /dev/null
+++ b/2021/10.hs
@@ -0,0 +1,43 @@
+{-# OPTIONS -Wno-type-defaults #-}
+module Main where
+
+import Data.List
+import Data.Maybe
+
+import Input
+
+
+closing :: Char -> Maybe Char
+closing '(' = Just ')'
+closing '[' = Just ']'
+closing '{' = Just '}'
+closing '<' = Just '>'
+closing _ = Nothing
+
+score1 :: Char -> Int
+score1 ')' = 3
+score1 ']' = 3 * 19
+score1 '}' = 3^2 * 7 * 19
+score1 '>' = 3^3 * 7^2 * 19
+score1 _ = 0
+
+score2 :: Char -> Int
+score2 = fromMaybe 0 . fmap succ . flip elemIndex ")]}>"
+
+data Result = SErr Char | Incomplete String | Ok
+ deriving (Show)
+
+parse :: String -> Result
+parse = go []
+ where go s (c : cs) | Just cl <- closing c = go (cl : s) cs
+ go (c:s) (c':cs) | c == c' = go s cs
+ go _ (c:_) = SErr c
+ go s [] = Incomplete s
+
+main :: IO ()
+main = do
+ inp <- getInput 10
+ print $ sum [score1 c | SErr c <- map parse inp]
+ let middle l = sort l !! (length l `div` 2)
+ print $ middle [sum (zipWith (*) (reverse $ map score2 s) (iterate (*5) 1))
+ | Incomplete s <- map parse inp]
diff --git a/2021/10.in b/2021/10.in
new file mode 100644
index 0000000..27355e5
--- /dev/null
+++ b/2021/10.in
@@ -0,0 +1,102 @@
+[<[{<[(([<[[{[()()]}]{<<<>[]>[()[]]>{(<>[]){<>[]}}}]<{(<()<>>{()<>})(<()>)}([{()[]}](<()<>>
+<[(<({[<(<<({({}[])[<>]}[<<>{}>[()()]])>>)>]})>{[([({[{{<[[]{}]{{}}><{()[]}[{}]>}}{{[<<>()>((){})
+{<({([<([[<<[(<>())({}{})](<()()>{{}})>(([[]{}]<[][]>){<{}>{<>{}}})>]][[((<[<>()]<<>[]>>{{()[]}{[]{}
+([{({<<{<<<{([{}[]]([]())){[(){}]}}{[<{}()>(<>[])]}][({[()<>][<><>]}{{{}[]}})<<<{}()>>>]>([[<[{}<>]
+{([{({(<{[<(<(()()){{}()}>[(<><>)<<>[]>])[{{{}()}[(){}]}[<()[]>[{}[])]]>{([{{}{}}{[]}][{{}<>}{<><>}]){[[[]()
+[{(([[{([(({(<{}()>({}<>))((()())(<>[]))}{<{{}[]}[{}()]>{{()()})})<{{([]{})[<>[]]}[{<>[]}{
+<<([{{({{{[(<[<>()][()<>]>)]}<(<<<<>()><{}()>>><({{}<>}{()[]}){<(){}>}>)>>})<[{[<([[{}{}]{{}()}]
+<[{{[<[{(<<([([]{})]<[[]{}]{<>()}>)(<<<>{}>{{}[]]>(<[]()>(()[])))><<[{[][]}{[]}](([])([]))><({{}{}}{[][]})
+{{{({{{([<<<{[()]({}{})}((()[])<()<>>)>{{<{}<>><{}()>}}>(<<(())({}())>{{{}}({}())}>{<[{}<>]<{}{}>>[{<>()}
+{<({<[{[<<{{[[[][]][<><>]](([]{})<()[]>)}<<((){})><[[][]](<><>)>>}{(<<{}<>><<>>><((){})([]<>)>)<(([]))(
+({{{([({<((<<<()>[[]<>]>(<<><>>(()()))>))>})]){({[<[<<[[{}{}]][([]<>)]><{<{}()><()<>>}(<[][]>[{}()])]>{({{
+(<{<<[[[(<{<({<>()}{{}<>})<<()()>(<>[])>>(({{}()}([])))}>([[<({}())({}())]((<>{})<<><>>)][[<(
+[([({{{[<([<[(<>[])[{}[]]]<[[]{}][<>]>>])<(((<()<>>(<>{}])({<>{}}[{}<>]))<([()()]{[]<>})({<>()}[{}
+<(<<([{{[<((({<><>}<<>>)[[[]<>]({}())]){(<<>()>{[]()})[<()>{[][]}]})>]<[[[{(<>{})<(){}>}[{<>{}}]]]][
+{[[[{[(((<{[{([]{})[[][]]}(<{}()><<>[]>)][<[<>{}]>]}>({([(()())<[]{}>](([]{})[<>{}])][[{[]{}}<<>{}>]({{}}[<>
+{{{([[<[({<<<({}{})<[]()>>[[<>[]>{<>[]}]>[({<>[]}({}<>))[[[]()][()<>]]]>})]>]<(<<<<[<((){})<{}{}>><{()()}((
+[{<<<[((<{{{[<{}{}>[{}{}]]([{}<>]{{}<>})}{{[{}{}][{}]}({[]<>}{<><>})}][([<[]<>><{}<>>][<(){}>(()
+[{<(<[{(<(<((((){})<[]<>>)[{()<>}{[]<>}])><(((<>)(<>[]))(<[]<>>))([<<><>>[[]<>]]{<[]()>{()[]}})>){<({{[][
+<(<<<[([[<{{(({}[])[<>{}])<(()<>)({}{})>}}>{{([(<>())<()[]>]{{[]<>}})<[[<>()]](<()[]>)>}<{[<{}<>><{}[]>](
+{((<[<[<(<[({{{}<>}(()<>)}{(<>{})[[]{}]})(((()[])))]>)[{([([<><>][{}[]])[<()[]>(<>[])]]({[
+[({([<([({<(<<(){}><{}<>>>{{<>[]}[()[]]})[[[{}[]](()())]]]({[{(){}}{()}]<{{}()}{{}()}>}[([[][]][()[
+({[[{[[({{[[(<<><>>{()}){[()()]}]<{{<><>}({}())}{{[][]}{()()>}>]<[{<<>[]>[[]<>]}]<[<()[]><(
+(<[{[(<{(<{{[{<><>}{[][]}](<(){}><[]()>)}}><{<(<<>()>([]<>))<({}<>){{}()}>>}{([(()[]}[<>[]]])<{{[]{}}
+<{{(<([(<<<<[{{}<>}(()[])][<{}[]>[<>[]]]><<{[]()}(()<>)>({()<>}({}[]))>><[(([]{}))[{<><>}([][])]]{{(<>())}(
+{<[(<{[[(<<[{<(){}>{<><>}}((()<>){<>()})]<[[{}<>]{{}[]}]{([])([]{})}>><{(<{}[]><()<>>)}<(({}()]{[
+[{[([([{{{{([(()[])[()()]])[[(<>{})[{}[]]]]}}}{<({[<()[]><{}()]]}{[[[]()]{()()}]})<<<[{}<>](<>[])>[(()<>)([]
+{(<{([<<<((({[{}<>]({}())}))[{{((){})[()()]}<{{}<>}<()[]>>}{{{[]()}}}]){((((()())(())){(<>{}){{
+{<<{{{([[<{<<[{}<>][<>[]]>>(([()()](<>[])){([]{})})}>{<((<<>()><[]<>>)({[][]}[[]{}])){(<(){}><{}>)(
+[[[{[{{{{[<{((<>())((){}))(([]{}){()()})}>([[[{}{}]{[]()}]{(()())<{}[]>}][{((){})<{}[]>}<<[]><
+(<[[<[{[<(<[<<{}[]>[[]<>]>((()<>)[<>[]])]{[[{}<>]({}{})](<[][]><[]{}>)}>([{(<>[])<{}{}>}({(){}}[()<>])]
+{{<[{({([[(([[{}<>][{}<>]][[<><>]]))<([({}()){[]()}](({}())<{}<>>))>]<{<(({}{})[[]<>])[<{}{
+[[({(<[<<{<{<({}())(()[])><((){})[()<>]>}{{<()>(<>[])}}><[([[][]]<()<>>)][<(<>())[()()]>{(<>())}]>)>((<<[
+[([{<<[(([((<<()[]><{}[]>>[{<>()}<()[])]){[{()[]}{<>[]}]{{<>}(()())}})<[(({}{})(()[]))(<[]
+((<<{{{<<[{[<<[][]>[<><>]>(({}<>)(<><>))](<<[]<>>(<>[])>[<<>{}>((){})])}]>>(({{([<<><>>{{}
+([<(([[[((<(([<>()]<()<>>)<[[]()][{}()]>){<(()<>){()()}>}>{(<(()()){{}<>}><<[]<>>[(){}]>)[<<{}{}>{[]
+({[<<[{<{<<<[<{}[]>]{[[][]]{[]()}}][{<<><>>(()())}({{}[]}<{}[]>)]>>((([<{}{}>({}())]({{}()
+{{[<<<[{(([<[<(){}><<>[]>]({<>[]}[<>{}])>]([<[[][]][[]{}]>({[]<>}[()<>])]))(([({{}()}{<><>})[[()()](<>[]
+[([{(<[<([[(<(()[]){(){}}>)[[<[]()>([]())]({[]<>}<{}()>)]]([<{[][]}(()<>)><[{}[]][()[]]>]<[<{
+(<[([<<<(<[({(())(()[])}<{<>()}{{}()}>)[[{()[]}<<>[]}]{[<>()][{}{}]}]]>{{[({<>[]})][([[]()]<{}<
+[[[<<{({[{{<[[[]()]<(){}>]{([])<()[]>}>[[({}[])[[]<>]][<(){}>[()<>>]]}{<(<[]()>{{}<>})<(<>[])({}
+<{[[<[[{[[(<<{(){}}({}<>)>({{}()}([][]))}([<[]{}>(<><>)]))<{{<[]<>>(()<>)}([[]()]({}[]))}({[<>{}
+(<[<[{{([{(<[[()()]]{{<>()}{<><>}}>(<[()[]]{[][]]>({<><>}<<>[]>)))((<<()[]>>)[[<{}[]>]<[{}()]<{}<>>>])}[
+{{{[<{[((<([<{(){}}{{}[]}>{[(){}][{}{}]}])<<[<<>[])(()())][((){})]>{({()[]}[[]{}])}>>){[({
+{(((<(<{(<<((<[]()>))({({}<>)({}<>)})>>)}>)><[[<[<[[{(<><>)({}())}(({}<>){()[]})]]{{[{<>{}}
+{{(<<(<([({(({[]{}}{{}[]})<(()())[()()]>)}<{{[{}<>](<>{})}{{{}()}{<>{}}})(({{}{}})(<[][]>{{}()}))>){[<[{<>()}
+[(<{<([[[<({[{<><>}{<>{}}][{()<>}{<>()}]}<(<()[]><()<>>)>)><<([[{}{}]]([<>[]][[]<>]))(<<<>()>[()<>]>
+({<{(<{[(<<(<([][])[(){}]>{({}<>)[{}[]]}){(({}[])[()()))(<[][]>(()<>))}>>)((<(<({}[]){[]()}>){({<>()}[{}
+{<[([<<[(<{((<{}<>>)(<{}[]>{{}[]}))}(<[<[]()>([]())]{[{}]<<>[]>}><[{{}<>}[{}[]]](([]<>)<{}{}>)>)>){
+[(({<([(<<[<<[[]<>]<()()>>{({})([]{})}>]<[{[<>()]{[]<>}}{{{}<>}<<>()>}]>>>((<{(<<><>>{[]{}})({<>[]}((){
+{[[([[{<<[[[<[<>{}]{<>()}>({{}()}[()<>])]]({{<{}[]><<><>>}{<()<>>}}{{{[]()}<()<>>}<(<>[])(()[])>}
+{<{<{{{{[[[((<{}{}>{{}{}})<{{}{}}{(){}}>)[[(()<>)]]]({{([]())[<>[]]}}[{<[]<>>((){})}([[]<>])])]
+<[({({[[<(<({([]<>)[<>]}[[()[]]([])])<(<(){}>(()[]))[<<>()>[[]{}]]>>>><{[{<[{}{}][{}()]>{([]())[<><>]}}<{<<
+[{<([<[(<({[<[<>]<{}[]>>{({}<>)[[]<>]}]{{{[]<>}(()[])}<(())>}}[({{[]()}{{}{}}}{{[]{}}[()[]]})])<{({{(){}}
+{{([(([{{{((<[()[]][<>{}]>[<<>()>[[][]]])<{<{}>[(){}]}{({}())[()()]}>)({({<>[]}<[]()})<({}{})<<
+(<(<{([<((<{<<{}<>>[()()]>({[]<>})}([[<>()]([]())])>{([{{}[]}(<>[])]{[[][]]{[][]}})}))>(<[{
+[({{{(<[{{{<(<{}>)<{<>()}<(){}>>>[[{()()}(()<>)][[[][]]([][])]]}}}((({((<>{}){{}{}))[{{}<>
+[<(([(<[{[<<({(){}})([<>[]){[]()})>>([[<()[]><{}>]])]<({[{()<>}<[]<>>][[<>()]]})>}]>)]{<{<(
+([(({({{{[[{(<[][]><{}<>>)}[((<><>)(()<>))<{<><>}{<><>}>]]{(([{}<>][[]()])<<[][]>([]())>){<[(){}]>}}][(<<
+({(<{<({{{<(<<[][]}>[{[]<>}{[]{}}])><(<(<>[])([][])>{({}<>)}){{<[]()>(()<>)}}>}(<<<<{}{}>[(){}]>[[()[]](
+<[<((<{{{<<{({<>[]}){<[][]><[]<>>}}{[{[]()}[{}[]]][({}())]}>[{<[()<>]>[{()[]}((){})]}(({[]()}
+[<({{[([([<{<[[]]<{}{}>>{([][])[()<>]]}[[<(){}><(){}>]]>((((<>{})[<>{}]){(()[])}){<[<>](()<>)>([[]<
+<[[([[[(({{<(({}){[][]})[[<>[]]([]())]><[<{}{}><{}()>]>}<(<{<><>}{()[]}>([{}()]((){})))>}{{([{{}}{<>[
+([[{<<<<(({(<([]{})<{}[]>>)}([[<{}()>)([[]{}]<<>()>)]{{{(){}}}[<()<>>{<><>}]}))<[{{<()()><{}{}>}}][{{<(){}><
+{[{{(<{{{<([[{{}()}{{}{}}]]({<[][]>(<>[])}[[[][]]{<>[]}]))>}}}>)}}{<[<{[{[<[({[]}<[]{}>){(<>{})(<><>)
+<{{([<{{{{<{{{()[]}{[]()}}{(())((){})}}{{(()[])[{}<>]}(<()<>>([][]))}>}}<[{({<()[]>({}[])}
+{(<([(([{{{({[()()]<()>}[([]()}<<><>>])[{[<>[]]<<>>}{{[]<>}(<>())}]}}<{{[[{}[]]]}(<<<>()>>({[]()}<<>[]>)
+<[{{{[{(<<(({<<>[]>{[]}}<{{}[]}<{}[]>>)[[([]())(<><>)][[[]()]([]{})]])[<{(()[])<()>}>([{{}{}}]{<(){}>(()())
+[(<[({<{[[{<{[{}[]]{[]<>}}[<()<>>[[][]]]>(<[{}<>]({}())><[{}{}]{()()}>)}((<<<>[]>(<>{})>[(<>())[{}{
+[[<{{<<[<<<<({{}<>}<{}[]>)((()[])[[]<>])><([<>[]]([]<>)){(<><>)}>>[({{()}{<>[]}}[([][])[{}[]]]){([{}()][<>{
+{{{<({[([({<[[{}<>](()())]([<><>]({}[]))>}(({<<>()>[[]]}[<()>{<>{}}])))]<{({{(()())<<>>}}[({[]{}}[
+(<<{(({{(<{{[<{}{}><<>()>]{{()[]}<<>{}>}}(<<{}<>><()>>{<()<>>([]{})})}<[{([]<>)<<>[]>}[<{}()><{}>]]>>
+{<[[<{[{(<{<<(<>)<{}{}>>>[<<{}()>({}{})>]}<<[({}[]](()[])]{<[]<>>(())}>{<{()<>}({}<>)>{<()
+[{((<<{<{[{[([()<>](()())){(<>())}}([[()<>][{}()]][({}[]){[]()}])}([<[()<>]([][])>[[[]{}]{()[
+[<[<[<<[([<{[{()<>}({}())]<{{}<>}([]())>}(<<<>{}>[{}{}]>[[[]()]])>]<({({(){}}<[]{}>)([()<>](()))}[({[
+[<[<[(((<(({{([][])}}<[[[][]]{(){}}>(<()[]>[[][]])>){([(()<>)<()()>]<[{}()]([]())>)<<{<>()}>([<>[]]{[]
+{{<{<[{[{[(<([{}()]{[]<>})({<>})>(({{}{}}([]{}))))<[[({}{})<()[]>][{[]{}}{(){}}]]{([()<>])(<()[]><<>()>)}>]}
+((({([{(<{<[[{{}<>}<{}()>]{([]<>)[{}[]]}]>(<([[]<>])((<>[]))>{<{[][]}(<>())>{{{}()}(()[])}})}>{[
+<{(([(<<<(<({{[]<>}{<>[]}}{[[]{}][[]{}]})>[<<[{}<>](()<>)><(()<>)[{}()]>>(<{<>[]]({}[])>{(<>)<[]{}>})]){[<<[(
+<{<{{<<<{((<([()()])(<(){}>{<>()})>)<([([]()){{}[]}]{{{}}<{}[]>})(<{()<>)>[<{}()>])>)(<(([()()](
+(<[{(<(<[<<[((<>[]){<>[]})<(<>[]]({}{})>][[{[]{}}{()[]}]]>>[<{(<[][]>{{}{}})}<([()[]]<[]<>>)[{<><>}<{}{
+({{<<({<<[<[<(<><>)<()<>>><[()<>]([][])>]>[{{<()<>><()<>>}}(<{{}()}><{{}{}}<{}{}>>)]]([[[{[
+([[<<([[<([{([()[]](<>[]))<<<>[])({}[])>}[{[[][]]}]])[<[[({}{})<{}<>>]]([{{}<>}({}[])](([]())({}{})))>[[
+<{<(<{({[({[[[()[]]{{}[]}][[<>[]>{<>[]}]]})]<{[{<[{}[]]{<>()}><([]<>){<>{}}>}{(<(){}>{<>{}})
+<<<[<{(<{(({({<><>}{{}<>}){([][])([][])}}[<{(){}}<<>{}>>{([]<>)[()[]]}>)<{{{<><>}{<>{}}}{(
+<[<<(({<<[<([<{}()><<><>]])<[[{}<>][<>{}]]<[{}<>](<>{})>>>](<(<[[]<>][(){}]>(<<>()>{<>})){[({}[]
+<[[{<[([[[[{([()<>])<[[][]]{[]{}}>}](<[(<><>)]>({{(){}}<[]()>}))]]]{<({{(<<>()><(){}>){<[]<>>}}}[[
+<{[[[(({{[{(([{}()][<>()]))[([[]{}]<{}[]>)([<>[]]{{}{}})]}[{[(()[])]((<>{}){()()})}<<{(){}}[[]<>
+(<((<[[{((({((()<>)){{{}<>}(<><>)}}<((()[]))>)([{(<>[])([]<>)}[([][])(<>[])]]<<<<>{}>>[([][])[{}<>]>>))([<
+[(((<[<{[([{(<<>[]>((){}))[[[]()][<>{}]])]<({<{}>{[][]}}{{{}<>}[<>[]]})<<{{}()}{(){}}>({<>{}}{{}[]
+{((<[{[<<<[{<[(){}]({}{})>}<[<[]{}>({}<>)][{(){}}<<>{}>)>][<[[{}]({}[])]>]><[{{{{}[]}}({[]{}}(<>
+[[<[(((({[[[({<>{}}{{}()})[<(){}>{<>}]]{(<<>{}>(()<>))([[]<>]<()<>>)}](<([[]{}]<()()>)>{<[()
+[<<<[{[<{[(({([][]){<>}}))(<{([]())[{}()]}[[{}[]]{[]<>}]><{(<>())<[][]>}[([][]){{}()}]>)](
+<(<{<<[([[<{[[<>()]<{}{}>][[(){}]<<><>>]}>]{(([[<>[]](<>{})>{<()[]><[][]>})[<[(){}]{[][]}><[<>()]([][]
+<[([<<[{{[<<<{<>()}[<>()]>[<{}{}>[{}{}]]>[{[(){}]}([[]{}])]>]}}]>>{<([<(({({[][]}){([]()){{}{}}}}
+[({{{((<{<{[<<{}{}>><<[]{}><<>{}>>][<{{}()}>]}[(<[[]]<<>[]>>[([]())<<>{}>]){<[{}[]]>((()<>)[[]{}
+{[<[[(({([[<[(<>{})<<>{}>]{<()<>><{}[]>}>[[{{}<>}([]<>)][({}())([]())]]]])[[({{[[]<>][<>{}]}[[<>
+(((<[[<<{{[[[([]{})<{}<>>]]{{[<>[]]<{}{}>}({<><>}{()()})}][[<<[]()>{<>[]}><(()())<()[]>>]{{([](
+[<{<[[[<<{[{<({})([][])>[{[]()}]}<[{{}()}[<><>]]>][((<[]{}><{}()>)(<<>()>))([<<>()>((){})>)]}{[({(<>())<(
+{([<[{{{<[{[({<>()}(<>{})}[{()()}[<><>]]]}<{{{<>[]}[{}[]]}({[]()}[{}()])}<({()()}<<><>>){{{}{}}
+{{<[[<({([{(([[]<>][{}<>])){{({}{})<<>()>}}}[[{[<><>][{}{}]}<{[][]}([]())>]<<[()[]]{()<>}>{<{}[]}(()())}>]
+<({<[([{[[<{<{[]{}}[<>]>}>([(<()[]>[[]<>])<{<>[]}>]{[(()())[{}]][<{}<>><{}>]})]]([{{{([]{})[(){}]}[<
+[<<[{[{{[[{[[[()<>][()[]]](({}<>)[()<>])]<<(()[])>([<>[]]{()<>})>}([<[{}{}]>{({}<>){[][]}}][{[<>[]][<>]}])]]}