summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTom Smeding <tom.smeding@gmail.com>2020-12-27 14:09:22 +0100
committerTom Smeding <tom.smeding@gmail.com>2020-12-27 14:09:22 +0100
commit833fcf24d661ef600d00c017ce7796b2fc938a17 (patch)
tree6e87577f23113e3be18fec3c6b297a9fbdc2dbb2
parenta03c0ce5608b23a351886efbbeaa30cef19c284f (diff)
Day 20
-rw-r--r--2020/19.hs3
-rw-r--r--2020/20.hs224
-rw-r--r--2020/20.in1728
-rw-r--r--2020/20.in.sample107
-rw-r--r--2020/Util.hs4
5 files changed, 2064 insertions, 2 deletions
diff --git a/2020/19.hs b/2020/19.hs
index 3ae886f..a3afb8f 100644
--- a/2020/19.hs
+++ b/2020/19.hs
@@ -34,8 +34,7 @@ matches :: Gram -> [Int] -> String -> Bool
matches _ [] [] = True
matches gram@(Gram arr) (r:rs) (c:cs) =
case arr A.! r of
- S c' | c == c' -> matches gram rs cs
- | otherwise -> False
+ S c' -> c == c' && matches gram rs cs
D alts -> any (\alt -> matches gram (alt ++ rs) (c:cs)) alts
matches _ _ _ = False
diff --git a/2020/20.hs b/2020/20.hs
new file mode 100644
index 0000000..73ebef5
--- /dev/null
+++ b/2020/20.hs
@@ -0,0 +1,224 @@
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE TupleSections #-}
+module Main (main, showLayout) where
+
+import Data.List (sortBy, transpose, intercalate, tails)
+import Data.Foldable (toList)
+import qualified Data.Map.Strict as Map
+import Data.Map.Strict (Map)
+import Data.Maybe (catMaybes, listToMaybe, fromJust)
+import Data.Ord (Down(..), comparing)
+import qualified Data.Set as Set
+import Data.Set (Set)
+
+import Input
+import Util
+
+
+data V4 a = V4 a a a a
+ deriving (Show, Functor)
+
+instance Applicative V4 where
+ pure x = V4 x x x x
+ V4 f1 f2 f3 f4 <*> V4 x1 x2 x3 x4 = V4 (f1 x1) (f2 x2) (f3 x3) (f4 x4)
+
+instance Foldable V4 where
+ foldr f z (V4 a b c d) = f a (f b (f c (f d z)))
+
+ifmap :: (Int -> a -> b) -> V4 a -> V4 b
+ifmap f (V4 a b c d) = fmap (uncurry f) (V4 (0, a) (1, b) (2, c) (3, d))
+
+(!*) :: V4 a -> Int -> a
+V4 a b c d !* i = [a, b, c, d] !! i
+
+data B = F | T
+ deriving (Eq, Ord)
+
+instance Show B where
+ show F = "."
+ show T = "#"
+
+newtype Border' a = Border { unBorder :: [a] }
+ deriving (Eq, Ord, Functor)
+type Border = Border' B
+
+instance Show a => Show (Border' a) where
+ show (Border l) =
+ let l' = map show l
+ in if all ((== 1) . length) l' then concat l' else show l
+
+data Rotation = R Int B -- rotated n, then possibly horizontally flipped
+ deriving (Show)
+
+data Tile' a = Tile Int Rotation (V4 (Border' a)) [[a]]
+ deriving (Functor)
+
+type Tile = Tile' B
+
+instance Show a => Show (Tile' a) where
+ showsPrec p (Tile i r v _) = showParen (p > 10) (showString ("Tile " ++ show i ++ " (" ++ show r ++ ") ") . showsPrec 11 v . showString " {...}")
+
+boolb :: Bool -> B
+boolb True = T
+boolb False = F
+
+notB :: B -> B
+notB F = T
+notB T = F
+
+tileID :: Tile -> Int
+tileID (Tile i _ _ _) = i
+
+parseTile :: [String] -> Tile
+parseTile [] = error "empty tile"
+parseTile (hdr:lns) =
+ fmap (boolb . (== '#')) $
+ Tile (if take 5 hdr == "Tile " then read (take 4 (drop 5 hdr)) else error ("tile header?" ++ show hdr))
+ (R 0 F)
+ (V4 (Border (head lns))
+ (Border (map last lns))
+ (Border (reverse (last lns)))
+ (Border (reverse (map head lns))))
+ lns
+
+-- Rotates clockwise 90 degrees
+rotArray :: [[a]] -> [[a]]
+rotArray = map reverse . transpose
+
+-- Flips horizontally
+flipArray :: [[a]] -> [[a]]
+flipArray = map reverse
+
+-- Rotates clockwise 90 degrees
+rotate :: Tile -> Tile
+rotate (Tile i (R rotn rotf) (V4 a b c d) e) = Tile i (R (rotn+1) rotf) (V4 d a b c) (rotArray e)
+
+-- Flips horizontally
+flipTile :: Tile -> Tile
+flipTile (Tile i (R rotn rotf) (V4 (Border a) (Border b) (Border c) (Border d)) e) =
+ Tile i (R rotn (notB rotf)) (V4 (Border (reverse a)) (Border (reverse d)) (Border (reverse c)) (Border (reverse b))) (flipArray e)
+
+type Cd = (Int, Int) -- coordinate
+
+data Layout = Layout (Map Cd Tile) (Set Cd)
+ deriving (Show)
+
+lput :: Cd -> Tile -> Layout -> Layout
+lput pos tile (Layout mp bd) =
+ Layout (Map.insertWith (error "lput: taken") pos tile mp)
+ (Set.delete pos bd <> (Set.fromList (toList (neighbours pos)) Set.\\ Map.keysSet mp))
+
+neighbours :: Cd -> V4 Cd
+neighbours (x, y) = V4 (x, y-1) (x+1, y) (x, y+1) (x-1, y)
+
+borderAt :: Cd -> Layout -> V4 (Maybe Border)
+borderAt pos (Layout mp _) =
+ ifmap (\i pos' -> (\(Tile _ _ bd _) -> Border (reverse (unBorder (bd !* mod (i + 2) 4)))) <$> Map.lookup pos' mp) (neighbours pos)
+
+densityAt :: Layout -> Cd -> Int
+densityAt ly pos = length (catMaybes (toList (borderAt pos ly)))
+
+matchesOutline :: Tile -> V4 (Maybe Border) -> Bool
+matchesOutline (Tile _ _ bd _) outl =
+ all id ((\b -> maybe True (== b)) <$> bd <*> outl)
+
+rotrefls :: Tile -> [Tile]
+rotrefls = concatMap (\t -> [t, flipTile t]) . take 4 . iterate rotate
+
+matchesAtPos :: Layout -> [Tile] -> Cd -> [(Tile, [Tile])]
+matchesAtPos ly ts pos =
+ [(t', rest)
+ | (t, rest) <- splits' ts
+ , t' <- rotrefls t
+ , matchesOutline t' (borderAt pos ly)]
+
+allCandidates :: Layout -> [Tile] -> [(Cd, Tile, [Tile])]
+allCandidates ly@(Layout _ bd) ts =
+ catMaybes
+ [case matchesAtPos ly ts pos of
+ [(t, ts')] -> Just (pos, t, ts')
+ _ -> Nothing
+ | pos <- sortBy (comparing (Down . densityAt ly)) (toList bd)]
+
+findCandidate :: Layout -> [Tile] -> Maybe (Cd, Tile, [Tile])
+findCandidate ly ts = listToMaybe (allCandidates ly ts)
+
+placeAll :: Layout -> [Tile] -> (Layout, [Tile])
+placeAll ly ts
+ | Just (pos, t, ts') <- findCandidate ly ts = placeAll (lput pos t ly) ts'
+ | otherwise = (ly, ts)
+
+extents :: Map Cd a -> ((Int, Int), (Int, Int))
+extents mp =
+ let keys = Map.keys mp
+ in ((minimum (map fst keys), maximum (map fst keys))
+ ,(minimum (map snd keys), maximum (map snd keys)))
+
+showLayout :: Layout -> String
+showLayout (Layout mp bd) =
+ let mp' = foldr (uncurry Map.insert) (Map.map Just mp) (map (,Nothing) (toList bd))
+ ((xmin, xmax), (ymin, ymax)) = extents mp'
+ in unlines [intercalate " "
+ [maybe "...." (maybe "----" (show . tileID)) (Map.lookup (x, y) mp')
+ | x <- [xmin..xmax]]
+ | y <- [ymin..ymax]]
+
+cornerProd :: Layout -> Int
+cornerProd (Layout mp _) =
+ let ((xmin, xmax), (ymin, ymax)) = extents mp
+ in product (map (tileID . fromJust . (`Map.lookup` mp)) [(xmin,ymin), (xmin,ymax), (xmax,ymin), (xmax,ymax)])
+
+squareOfTiles :: Layout -> [[Tile]]
+squareOfTiles (Layout mp _) =
+ let ((xmin, xmax), (ymin, ymax)) = extents mp
+ in [[mp Map.! (x, y) | x <- [xmin..xmax]] | y <- [ymin..ymax]]
+
+removeEdges :: [[B]] -> [[B]]
+removeEdges = map trim . trim
+ where trim = tail . reverse . tail . reverse
+
+joinEdges :: [[Tile]] -> [[B]]
+joinEdges tiles =
+ concat [map concat (transpose [removeEdges body | Tile _ _ _ body <- tilerow])
+ | tilerow <- tiles]
+
+monster :: [[B]]
+monster = map (map (\case '#' -> T ; ' ' -> F ; _ -> undefined)) pat
+ where pat = [" # "
+ ,"# ## ## ###"
+ ," # # # # # # "]
+
+fieldParts :: [[a]] -> [[[a]]]
+fieldParts bd = concatMap maptails (tails bd)
+ where maptails [] = []
+ maptails ([]:_) = []
+ maptails l = l : maptails (map tail l)
+
+exceedsLength :: [a] -> [a] -> Bool
+_ `exceedsLength` [] = True
+[] `exceedsLength` _ = False
+(_:xs) `exceedsLength` (_:ys) = xs `exceedsLength` ys
+
+matchPattern :: [[B]] -> [[B]] -> Bool
+matchPattern bd pat =
+ bd `exceedsLength` pat &&
+ all (\(bdrow, patrow) -> bdrow `exceedsLength` patrow &&
+ all (\(b, p) -> (p == F) || (b == T)) (zip bdrow patrow))
+ (zip bd pat)
+
+countPattern :: [[B]] -> [[B]] -> Int
+countPattern bd pat = length (filter (`matchPattern` pat) (fieldParts bd))
+
+numTrue :: [[B]] -> Int
+numTrue = length . concat . map (filter (== T))
+
+main :: IO ()
+main = do
+ tile0:tiles <- map parseTile . filter (not . null) . toList . splitOn null <$> getInput 20
+ let initLayout = lput (0, 0) tile0 (Layout mempty (Set.singleton (0, 0)))
+ (ly', _) = placeAll initLayout tiles
+ print (cornerProd ly')
+ let image = joinEdges (squareOfTiles ly')
+ images = concatMap (\b -> [b, flipArray b]) (take 4 (iterate rotArray image))
+ print (numTrue image - numTrue monster * maximum (map (`countPattern` monster) images))
diff --git a/2020/20.in b/2020/20.in
new file mode 100644
index 0000000..908ad8b
--- /dev/null
+++ b/2020/20.in
@@ -0,0 +1,1728 @@
+Tile 3593:
+#..#.##...
+.#..#.#...
+.#####..#.
+.......#.#
+#...#.....
+..#.....##
+.#....#...
+.#..#.....
+..#......#
+#.####.##.
+
+Tile 3041:
+####.#.###
+#..#..#.#.
+.......#.#
+#.....#...
+....#....#
+.#.......#
+#..#.....#
+#...#.....
+##........
+##.##...##
+
+Tile 3761:
+...#..##.#
+#....#..#.
+........#.
+#..##.....
+#..#.....#
+.#....#..#
+#.#....#..
+#....#....
+.....#...#
+#.#####..#
+
+Tile 1307:
+...#######
+#......#..
+........#.
+#.#......#
+#........#
+..........
+#....#....
+#..#..#..#
+...#.##...
+.....##.#.
+
+Tile 3709:
+#.##.#####
+##....#...
+..##.#..#.
+....#.....
+#..#..#..#
+.........#
+.........#
+##.##.#.#.
+...###....
+#####.#...
+
+Tile 2381:
+.....#.##.
+#........#
+....#..#..
+...#.#..##
+.......###
+...#.....#
+.##.......
+....#.....
+......#..#
+#.#######.
+
+Tile 3089:
+.....#..##
+#....###.#
+........##
+......##.#
+#.#...#..#
+....##...#
+#...#.#...
+##.......#
+..#..#...#
+#...####.#
+
+Tile 3049:
+##.#.##.##
+.#...#..#.
+.#..##..##
+...##.....
+....#...##
+#......###
+#...#..#..
+#.......#.
+........##
+##.##..#.#
+
+Tile 1171:
+#..#.##...
+.#.......#
+##......#.
+.##..#.#.#
+#...#..#.#
+.....#..#.
+.#..#.#...
+.#........
+....##..#.
+#.##...###
+
+Tile 2903:
+#....#####
+..#....#..
+..#...#.##
+#...#....#
+..##.#..##
+.#.#..#..#
+..........
+#...#.##..
+#.......##
+###..###.#
+
+Tile 3259:
+#..######.
+..##.#..#.
+#..#....##
+....#....#
+#........#
+.......#.#
+##.#..#...
+#..#...###
+.....#...#
+##...###.#
+
+Tile 2083:
+.#.#...#..
+.#.......#
+.........#
+#......#..
+#.....#...
+....#...##
+##....##..
+.#.....#.#
+.###......
+...#..####
+
+Tile 1019:
+##...##..#
+..#.#.....
+#..#...#..
+#......###
+.........#
+..##....##
+####..#..#
+#.#..#..#.
+#..#....#.
+.#.#.###..
+
+Tile 2659:
+..#....#.#
+##.#...#..
+.##...##.#
+..#.#..#.#
+#.##..#.#.
+.......#..
+#.##......
+#..#.#..#.
+..#....#.#
+...#.###.#
+
+Tile 1873:
+##.#####.#
+..#....#..
+..........
+.......#.#
+..#....##.
+.......#..
+.#....#...
+#.......##
+#.#.......
+#.#....#..
+
+Tile 2851:
+#.#..#..##
+#.#...#.#.
+##.....#..
+#...#.....
+.#....#...
+....#..#..
+...#....##
+#.##..###.
+.#..##.#.#
+.#..#....#
+
+Tile 3529:
+####....##
+.....##..#
+...##.#.#.
+#.#..###.#
+#.#....##.
+....#..###
+#......#.#
+##......##
+#.#.....##
+.#.####..#
+
+Tile 2221:
+.#...#.###
+##.##..###
+#.........
+.........#
+#........#
+......#..#
+......#...
+..##..#..#
+.....#.#.#
+..#.######
+
+Tile 3251:
+####.#.##.
+#..#....#.
+#....#.#.#
+.....##..#
+..........
+#...#..#..
+....######
+..#.#....#
+...#....#.
+##.#.#...#
+
+Tile 2693:
+..###.####
+.#....#..#
+..##......
+##.##...##
+.#....#...
+#...#....#
+##..#.#..#
+.##......#
+.##.###..#
+###.#..#.#
+
+Tile 1187:
+.#..###.##
+..#.#.#..#
+#.#......#
+...#..#..#
+#.....##..
+#......#.#
+##.....#..
+......#..#
+..........
+#..##.....
+
+Tile 1237:
+####....#.
+.#........
+.#..###..#
+#.#.....#.
+#........#
+....#....#
+..#...#..#
+#...##....
+.#.#.#...#
+.##..#....
+
+Tile 1163:
+#.#..#.#..
+...#.###.#
+.#...#..#.
+#...###...
+...#......
+...#..#...
+#...#....#
+#....#...#
+#...##..#.
+#.######..
+
+Tile 2113:
+.##.#..###
+#.#..##..#
+.......#..
+#....#....
+##........
+#....#...#
+......#...
+#......#..
+#...##...#
+#.##..####
+
+Tile 3989:
+#..###.###
+#.....#.##
+#.........
+##........
+#.........
+#..#......
+.....#...#
+......#...
+.#..#.....
+#..#######
+
+Tile 3163:
+##..#...#.
+...#..#..#
+##.#.....#
+.#....#.#.
+#...###.#.
+#....#....
+...#.....#
+#..#.#...#
+#..#......
+..#..#####
+
+Tile 2137:
+####..##.#
+...#......
+........##
+...#..#.##
+#.#..#.#..
+.#..##...#
+.#.#.###..
+#...#.....
+...##....#
+.#..#..#.#
+
+Tile 1087:
+.#.##.####
+..###.#...
+#...#.....
+##.......#
+#......#.#
+..#.......
+#.#...#...
+#...#....#
+#.#......#
+.#..######
+
+Tile 1613:
+.##..#####
+..#.####.#
+#...#....#
+.#...##.#.
+#.#.....#.
+#.#..#...#
+#.#.......
+.##.....##
+.....#...#
+#..#.##.##
+
+Tile 3613:
+#......###
+.....#....
+.........#
+#.#......#
+.###....##
+.#..##.#.#
+#...#....#
+#......#..
+.........#
+....#.....
+
+Tile 2293:
+#......#.#
+#.....##.#
+.....#...#
+#........#
+.#....##.#
+#.#..#.###
+.#.....#..
+.........#
+#.#.......
+#....##..#
+
+Tile 3373:
+#####...##
+..#..#...#
+.........#
+...#......
+##.#.....#
+#.........
+#.#....#.#
+....#.....
+..##.#..#.
+..#.#.#..#
+
+Tile 2539:
+#.##.####.
+#.##..#..#
+#....#...#
+#...##...#
+.#....#..#
+.#........
+.......##.
+#.....#...
+.....#...#
+.#.....#..
+
+Tile 2833:
+.#..#.##..
+#.........
+.........#
+.#.###.#.#
+##..####.#
+.....#.#.#
+...#.#....
+.#...#....
+#.........
+..####..##
+
+Tile 3019:
+#....##..#
+.....#...#
+#..#..#.#.
+..##.....#
+..####...#
+###...##..
+#.#...##..
+..##...#.#
+.....##...
+#.##...#..
+
+Tile 3061:
+.#...#..#.
+....###...
+....###.##
+...#.#....
+....#.#...
+.....##...
+#.......##
+..#.##.#..
+#.#....#..
+###..##..#
+
+Tile 2593:
+#...####.#
+...##..###
+.....#.#..
+#...##..#.
+#..##.....
+..........
+#.......##
+#...#....#
+..#..#....
+.#.#####.#
+
+Tile 2617:
+......###.
+..#...#..#
+.#...#...#
+....#.....
+#.....##.#
+.#.....##.
+..##......
+..#.#....#
+##.......#
+##.##.##..
+
+Tile 1823:
+#####....#
+....#...##
+........##
+.......###
+..........
+###.#.....
+.......#.#
+..#...#.#.
+........#.
+##.......#
+
+Tile 3191:
+.#.#..#.##
+...#......
+..#......#
+#.#......#
+...#...###
+....##.#..
+..###....#
+#..#.#.#..
+##.....#.#
+#..#####..
+
+Tile 3371:
+###.##..##
+.#..#..#..
+....#.....
+.......#..
+.........#
+#..##.....
+.....##.#.
+.##.##.#..
+#........#
+#.###..#..
+
+Tile 1721:
+.#.##.##..
+##..#...#.
+##........
+#....###.#
+..#.#...#.
+.#.......#
+#.....##..
+#.......##
+.#..#...#.
+##.##.#..#
+
+Tile 3011:
+#.##.#.###
+..........
+.....##...
+........##
+#..#......
+.#......#.
+.......#..
+#........#
+#...#.....
+......####
+
+Tile 1801:
+#.#.#.####
+#..#.#....
+.#...#..#.
+.##...#..#
+##........
+#.#.##..##
+##..#.....
+#...#....#
+##.##...#.
+#######.#.
+
+Tile 1129:
+.###.##.##
+.....#...#
+.#........
+##...#....
+###..#.###
+##........
+#.###....#
+.#......#.
+......#...
+#....#..#.
+
+Tile 3517:
+#..#.#..##
+#.....#.##
+...#.#...#
+#..#.....#
+##.#.....#
+.#.....#.#
+.##.###...
+..........
+#....#..#.
+.######..#
+
+Tile 3607:
+##..#.#.##
+#....#...#
+#..##.....
+.........#
+..#.......
+#...#.....
+#....#..##
+#....##...
+#..#.#.#..
+..########
+
+Tile 2803:
+..##.#.##.
+...##....#
+....#....#
+..#..#.#.#
+#..##.....
+#....##..#
+.....#...#
+#...#.....
+#...#.....
+.#.#.#.#.#
+
+Tile 3331:
+.#####....
+#.........
+.#..#.....
+....#.....
+#......#..
+#.......#.
+...#.#....
+#.........
+#.......##
+#.#..#####
+
+Tile 3499:
+#...#.#..#
+.#........
+#...####.#
+.#..###...
+#..##.##.#
+.##.......
+..........
+....#..#.#
+...###...#
+..#....###
+
+Tile 3299:
+.......##.
+..#.#.....
+.#.....##.
+#.........
+..........
+##........
+#...#..#.#
+...##.....
+.......#.#
+#.##.###.#
+
+Tile 3793:
+#.##.####.
+#.........
+#...#.....
+#.#...#..#
+#.#..#...#
+....##.#..
+##...##..#
+......#..#
+..........
+.#.#######
+
+Tile 2657:
+#####.##..
+##....####
+...#.#....
+....###.##
+#.....#...
+..........
+#..#.#....
+.#...#....
+....###...
+.#.....#..
+
+Tile 2239:
+..###..#.#
+#.###.....
+#..#.#..#.
+#......##.
+#.........
+..........
+#...##....
+...#.#.#..
+........##
+#....#.#.#
+
+Tile 2861:
+#...#####.
+........##
+#.....#.#.
+#........#
+......#...
+##..#..#..
+.##......#
+.#.##...##
+..#......#
+.....#.#.#
+
+Tile 1061:
+#....###.#
+.......#.#
+.#..###..#
+.....#...#
+.........#
+#.....#..#
+#.#......#
+....#.....
+##...#...#
+#.#.###.##
+
+Tile 1447:
+#.###.##.#
+#....##..#
+#.#...#...
+##......##
+#.......##
+##........
+.#.#....##
+.....##...
+##..##...#
+..###.#...
+
+Tile 1997:
+.#.#...##.
+#....#.#..
+..##..#...
+#####.....
+#....#....
+#.........
+..#..###.#
+..##...#..
+#....#.##.
+....#..##.
+
+Tile 2251:
+..##.#...#
+..........
+..#....#..
+#.#.#.#..#
+#.#.....#.
+##......#.
+#..#.#####
+.........#
+#....#....
+##.#.##.#.
+
+Tile 3797:
+####.#.###
+...##.....
+......#...
+#....#..##
+..#..###..
+.#.....##.
+#......##.
+..###.....
+.##.....##
+..##.##.##
+
+Tile 1669:
+.#.#..#..#
+#...#.....
+#.#.......
+#......###
+#.....##.#
+....#....#
+.....#..##
+...#..#..#
+.....#....
+###.#.....
+
+Tile 2939:
+#..#.###.#
+#........#
+###....#..
+###...##..
+#.##.#..##
+.##..#....
+#.......##
+#.#...#..#
+##......#.
+..##...###
+
+Tile 2411:
+###..#.#.#
+#...##....
+##...#...#
+.#.#..#...
+#.....#...
+#.#.##....
+.......#.#
+.###......
+##...#.###
+##.#.#.#.#
+
+Tile 3469:
+#.#..#...#
+.........#
+#.........
+##.#####.#
+......#...
+..........
+#........#
+...#.....#
+#........#
+#..#.....#
+
+Tile 2677:
+.#.#.#..##
+#...#.#..#
+..........
+...#..#..#
+..........
+..........
+##.#.....#
+#........#
+#.....##.#
+##.#..##..
+
+Tile 3361:
+.#..#...##
+#.#....#..
+...####...
+.#...#...#
+#..#....#.
+#........#
+#.##.....#
+.#...#..##
+##.....#..
+##.....#.#
+
+Tile 1567:
+#...#.###.
+#.#.#.....
+#.###.#..#
+..........
+......#.##
+#.........
+.#...##...
+###.##...#
+#..#....#.
+..###..#.#
+
+Tile 1153:
+##.#..##.#
+####..#..#
+#.........
+....#...#.
+#...#..#..
+#........#
+.#......#.
+#......###
+....####..
+###...#.##
+
+Tile 1063:
+#.###..##.
+.......#.#
+......##.#
+...#..#.##
+#.....#.#.
+.....#....
+......#..#
+.#......#.
+#.......#.
+#...#.####
+
+Tile 3643:
+#.#.##....
+......##.#
+#.....#...
+.....##.##
+#....##.##
+......#...
+.##....#.#
+#..#...#..
+..........
+#...###.#.
+
+Tile 2161:
+####.###..
+..#...###.
+##.......#
+#....#...#
+#.....###.
+..........
+...#....#.
+##......#.
+......##..
+#.#..####.
+
+Tile 1373:
+#########.
+.#.#.....#
+..........
+#..#...#.#
+#....#....
+#....#..#.
+..#.......
+#.......##
+#..#..###.
+##...#....
+
+Tile 2237:
+.#..#...##
+#..#.....#
+#......#.#
+....#..#..
+.....#....
+#..#.....#
+###.......
+#...#.....
+#.........
+##...#.#..
+
+Tile 3319:
+.##.####..
+#.....#...
+#..#......
+.......#..
+..........
+#.#......#
+#.....#...
+#.##......
+....#.#..#
+#...#.##.#
+
+Tile 1931:
+###.....#.
+...##.....
+.........#
+....#.#.#.
+.....#....
+....#.#...
+##.......#
+#....#.#.#
+..........
+####.#...#
+
+Tile 2753:
+#..##.....
+.#.......#
+#.....#...
+.#.....#.#
+##..#..#..
+....#.#...
+##.#.....#
+.##..#....
+......#...
+.#......##
+
+Tile 2273:
+.#.######.
+.#..#....#
+#..#.##...
+.#...##..#
+..#.##....
+#....#....
+#...###.##
+#...#....#
+#......###
+#.#.####.#
+
+Tile 2131:
+..#.##.#.#
+........##
+#.#..#...#
+......#..#
+#.....#..#
+..........
+.........#
+...#.#..##
+#.#.......
+#.##.##..#
+
+Tile 1259:
+#....#.###
+#........#
+#...#.#..#
+.#.#...#.#
+...#.#...#
+.#..#..#..
+......#...
+.#....####
+#.....##..
+.#.#.##..#
+
+Tile 2837:
+##.....###
+#.#..#..##
+#..##....#
+#.........
+#.........
+#..#.#.#..
+#.........
+......##.#
+#.......#.
+##.###...#
+
+Tile 3467:
+#.#.##..##
+#.#.#.#..#
+#.#......#
+##.#.....#
+.......#.#
+.#....####
+.......#.#
+#.#....#.#
+....#..#..
+#...##....
+
+Tile 3833:
+..#.###.##
+#....###.#
+#....#.#..
+##......##
+.........#
+.........#
+#...##..##
+#......#..
+#..#...#..
+##.#.##.##
+
+Tile 1559:
+###.##..#.
+#..####..#
+.....##.##
+#..#.....#
+..........
+#..###....
+.#..#..#..
+#.##..#.#.
+#..#.#....
+##.#....##
+
+Tile 1483:
+#.#.###..#
+#..#...#.#
+#.....#.#.
+#........#
+#...#..#.#
+#.#..##.#.
+#.#.##...#
+......#.##
+.....#..##
+#.#.#.##.#
+
+Tile 2711:
+...###..#.
+#..#......
+........##
+#.#...#..#
+#.....#...
+...#.##..#
+#.........
+##.##.....
+#....#..#.
+#.#####.##
+
+Tile 1321:
+...#.####.
+....#...##
+...#.#..#.
+###....#.#
+#....#.#..
+#....#.#.#
+..#....#.#
+#.........
+#...#....#
+#.#..#.###
+
+Tile 1637:
+#.#...###.
+.#......#.
+#..#..#.#.
+.#........
+.#......##
+####.....#
+#.##.....#
+###..#....
+.##..#...#
+##....####
+
+Tile 2687:
+..##....##
+.#.....#.#
+.#....#.##
+#.#..#...#
+...#.....#
+#...#.....
+#......##.
+##.#..##.#
+..##.#..##
+###.######
+
+Tile 2543:
+...#####.#
+#.#...#...
+.......#..
+.#..#.#.##
+.#.#......
+###..#...#
+#..##...##
+#.#.#.##..
+.....#...#
+#...#..##.
+
+Tile 1487:
+...#..###.
+....#....#
+...#...#..
+##..#.#.#.
+...#...#..
+...#.#.#.#
+#.........
+#..##.#...
+.#.#......
+#...##.#.#
+
+Tile 3929:
+#.#.#.#.##
+.#.##..#..
+...##....#
+....#.....
+.....#...#
+.#.#....##
+.#..#.....
+#..#......
+##....#...
+.#.###.#.#
+
+Tile 3617:
+##.##...#.
+#..#..####
+#.........
+#..#....##
+...#.....#
+.#.......#
+..#.......
+.##..#...#
+.##......#
+#......##.
+
+Tile 1069:
+#.#.#...#.
+##.#...###
+##.......#
+...#...#.#
+#.#.....#.
+#..#..#..#
+#.###..#.#
+#.##..##.#
+.#......##
+.#.###.##.
+
+Tile 3863:
+.#.#.....#
+..#.#..#..
+...#.#..#.
+.....##...
+#........#
+#......##.
+...#....##
+.......###
+....#.....
+#####..###
+
+Tile 1847:
+.###.#....
+#........#
+#........#
+#.#.#.....
+##..#.#..#
+#.....#..#
+..#.#..#..
+##...#.#..
+#........#
+###.#...##
+
+Tile 1831:
+.#.##.#..#
+..#.#..###
+#.#.......
+#.........
+.....#....
+#.........
+#....#..##
+#......##.
+#....#...#
+...#..###.
+
+Tile 3697:
+....###..#
+##.#..#..#
+#.#...####
+#.......#.
+#.##.#....
+#..#......
+#.........
+...#.....#
+#.........
+.######.##
+
+Tile 1433:
+..##.#.#.#
+..#.....##
+......##..
+...#..##.#
+....##....
+#.#.#..#.#
+....###...
+#.........
+..#...#...
+.#.##....#
+
+Tile 1987:
+..##......
+..#..#..#.
+.........#
+.....#....
+..##.....#
+.........#
+....##...#
+#......##.
+#........#
+..####..##
+
+Tile 2389:
+#.#.####.#
+#.....#...
+#....#....
+#....#....
+#...#.#..#
+##.#...#..
+.........#
+#.....#...
+#.#..#....
+..##..####
+
+Tile 3917:
+.##.##....
+#.#.....##
+..#..#..#.
+.#....####
+##.#...#.#
+.....#.#.#
+........#.
+#.###.....
+.#........
+.###..#.##
+
+Tile 3533:
+#.#...#.##
+#.........
+#.........
+###.##....
+.#.#..#.#.
+..........
+#....#...#
+#...##...#
+..#.##..##
+..###.#.##
+
+Tile 1471:
+#...##..##
+.#.##...#.
+#.#.......
+.......#..
+#.#......#
+#..##..#..
+###....###
+..#.#...#.
+##......#.
+.####.###.
+
+Tile 1051:
+#.#.##.##.
+###....#.#
+....#...##
+..#...####
+#.....####
+#........#
+#..#..#..#
+#......##.
+#...#.#.##
+####.#..##
+
+Tile 3407:
+#.#..#.#.#
+#........#
+..#..##...
+......#...
+#.........
+...#.....#
+#.##..##.#
+.......#..
+#.......##
+.....###..
+
+Tile 3853:
+###...#.##
+#.........
+.....##..#
+..#......#
+.....#...#
+....#...#.
+....#.....
+#........#
+.........#
+.##.##..##
+
+Tile 3079:
+.#.#..###.
+.....##...
+.....###..
+#....#.#..
+#.#.##...#
+#......#.#
+#.....#..#
+#........#
+.##.#..###
+#.#..##.#.
+
+Tile 3449:
+...##.#.##
+.#...#....
+#.......##
+##.#.....#
+#...#.#..#
+..#.#....#
+.#.......#
+..#....#.#
+...#.....#
+..#.###.#.
+
+Tile 2203:
+..#.###...
+#..#.....#
+#.##.#..#.
+........##
+...#...#.#
+.........#
+#..#..##.#
+#..##.###.
+...#...#..
+...###.###
+
+Tile 3067:
+#.####.##.
+.....#...#
+#..##...##
+#.#......#
+##..#..#.#
+###...#...
+..#.....##
+..#......#
+#.......##
+#.#.#...##
+
+Tile 3947:
+...#......
+###.......
+.#...#..#.
+#..#.....#
+#.#.......
+.##.......
+.......#..
+.#.#...###
+.#.....#.#
+.#......##
+
+Tile 1091:
+.##...##.#
+.#.#....##
+.........#
+#........#
+.#.......#
+#.......##
+#.........
+.#......##
+....#..###
+..#...##..
+
+Tile 1201:
+.##.#....#
+#......###
+..#.#..#.#
+#.....#..#
+.#.#.##.##
+##..#.##..
+.#......##
+##....#..#
+..........
+##.###....
+
+Tile 2281:
+##.#.....#
+.#..#...#.
+.#.....#..
+##..#.#..#
+#.#.#....#
+..........
+..##.#...#
+.#...##..#
+#...#.#...
+###.#..###
+
+Tile 3229:
+#...###.##
+##........
+..##.#.###
+.#.#..####
+#.#.....##
+...#......
+#.#.#.#..#
+#....#.###
+#.....#.#.
+#.##.##...
+
+Tile 3739:
+###.###.#.
+#..#....##
+#...#....#
+.....#.#.#
+.....#..##
+..........
+##.#.....#
+###..#.#..
+...#..#...
+.#.....#.#
+
+Tile 2069:
+.##.#.####
+#...#..#.#
+...##.....
+#...#.....
+.##.......
+#...#....#
+.#....#..#
+.#......##
+#.....#..#
+..#.##.#.#
+
+Tile 2399:
+####.#.#..
+.#....#..#
+#........#
+#.#.##...#
+.#....####
+##.#...#..
+#..#.##.#.
+...#.#.#..
+##.##..#..
+##..#..###
+
+Tile 2087:
+..#..#....
+..##.....#
+#.#.......
+###.......
+...#...#..
+..#.......
+##....##..
+#.#..##.##
+..#.#.....
+###...##.#
+
+Tile 3203:
+.#.##..#.#
+#..##....#
+#.......#.
+#..#......
+....##.##.
+..........
+..#..#...#
+.#....##..
+.....#.###
+#.###..#..
+
+Tile 3631:
+#####.####
+#.#..#...#
+##......##
+#.#..##..#
+.#......#.
+#.#...#...
+....#....#
+#.....##..
+....##....
+##..#...#.
+
+Tile 1291:
+.####..###
+#...#.#...
+.....#..##
+#..#.##.#.
+.##.......
+....#....#
+.........#
+.#....#.#.
+......#...
+#...#...##
+
+Tile 2377:
+....#..#..
+#...#..#.#
+#...#.....
+#........#
+.....#....
+##.......#
+##........
+#....#.##.
+#..##....#
+###..#....
+
+Tile 1223:
+##.#.###.#
+#..#..#..#
+.........#
+#.#.......
+...#......
+...#...#..
+#.#.......
+.##.####..
+...##.#..#
+#.#..##.##
+
+Tile 3343:
+..#..#..##
+.....##..#
+#.....#...
+.#.....#.#
+....#..#..
+........#.
+.#.#..###.
+##...##...
+#..#..#..#
+#....#..##
+
+Tile 3001:
+.#..#..#..
+##.#....#.
+#.#......#
+.....##...
+#..#..#...
+..#.#..###
+...#......
+...#...#.#
+.#...#...#
+##.##.###.
+
+Tile 3881:
+.#...####.
+#....###..
+.#..#..#.#
+...#.....#
+#..#......
+#...#...##
+.#.####.##
+#...#.#..#
+.#........
+#.#.###.##
+
+Tile 2897:
+#...#..#.#
+........##
+....#..#.#
+#....##..#
+....#...#.
+......#.##
+#.##.....#
+.....##..#
+.........#
+.#..#.....
+
+Tile 2819:
+#......#.#
+#...##....
+.......#..
+#..#......
+...##..#.#
+#........#
+#........#
+#..#..#..#
+.#.##.##.#
+#..###....
+
+Tile 1597:
+#######...
+#.###....#
+...###..#.
+#.....#..#
+..........
+..#......#
+#...###.##
+#........#
+.#.....#..
+..#..#.##.
+
+Tile 3461:
+#.#..#..#.
+...#..#..#
+###.#.#...
+.#..##....
+..##.....#
+.....#....
+.........#
+...#......
+#...#....#
+#.##.##.##
+
+Tile 2843:
+.#########
+.........#
+#.........
+...#..##..
+...##....#
+..........
+#..##....#
+#.##......
+.#.#..##..
+..###.#.##
+
+Tile 2309:
+.#.#...##.
+#.......##
+.......#..
+...#..#..#
+.###...##.
+##........
+....#....#
+#.#..#....
+#.#..#..##
+#...##.###
+
+Tile 1951:
+#..###..##
+#...#..###
+...###...#
+##...###..
+#.#......#
+..#.##....
+...#..##.#
+##......#.
+...#...###
+.#.#.##..#
+
+Tile 2027:
+####.##..#
+..#..#....
+#.#......#
+...#......
+##.#.....#
+...#...##.
+#..#......
+#.##...#.#
+..#...##.#
+.###......
+
+Tile 1097:
+.##.#.##..
+..#..#.##.
+...#..#...
+#........#
+##.#....#.
+#...#..###
+..#......#
+#.........
+..#......#
+....###...
+
+Tile 1181:
+.###..####
+#...##..#.
+#.##.#..#.
+#...#...#.
+#...#.....
+.#.....#.#
+.........#
+##........
+....#....#
+#..#.##..#
+
+Tile 3637:
+..####...#
+.........#
+#..##.#.#.
+#...#...##
+...###...#
+...#.....#
+..##.....#
+..##..##..
+#..#...#..
+#.#...####
+
+Tile 2957:
+#####.####
+.#....#...
+.....#....
+#..#..##.#
+...#.##..#
+#.....#.#.
+.....#..##
+#####....#
+#..#.#...#
+###..#...#
+
+Tile 1381:
+#.#...###.
+..#..#..##
+....#.#.#.
+#....#.#.#
+.###......
+#....##...
+#...#..#..
+..#..#..#.
+........#.
+#.#.##..#.
+
+Tile 2699:
+..##.####.
+..#..###.#
+.#......#.
+....#.#..#
+.#..#....#
+..##..##..
+#.....#..#
+###......#
+#.#.###...
+########.#
+
+Tile 2333:
+..#..#..##
+.#....#.##
+.....#....
+...#.##...
+#........#
+....##..##
+#....#.#.#
+#.........
+..#..#.##.
+######.#.#
+
+Tile 2467:
+.##..#.##.
+##...#....
+........#.
+..#..#..#.
+##..####..
+.#..#.#..#
+..........
+...#...#.#
+.#........
+.#..#.#...
+
+Tile 1123:
+#.######..
+..#.#.....
+.........#
+#.........
+....#..#.#
+.....#..##
+.....#....
+#..###...#
+#.#.##...#
+##...#.###
+
diff --git a/2020/20.in.sample b/2020/20.in.sample
new file mode 100644
index 0000000..b3aed46
--- /dev/null
+++ b/2020/20.in.sample
@@ -0,0 +1,107 @@
+Tile 2311:
+..##.#..#.
+##..#.....
+#...##..#.
+####.#...#
+##.##.###.
+##...#.###
+.#.#.#..##
+..#....#..
+###...#.#.
+..###..###
+
+Tile 1951:
+#.##...##.
+#.####...#
+.....#..##
+#...######
+.##.#....#
+.###.#####
+###.##.##.
+.###....#.
+..#.#..#.#
+#...##.#..
+
+Tile 1171:
+####...##.
+#..##.#..#
+##.#..#.#.
+.###.####.
+..###.####
+.##....##.
+.#...####.
+#.##.####.
+####..#...
+.....##...
+
+Tile 1427:
+###.##.#..
+.#..#.##..
+.#.##.#..#
+#.#.#.##.#
+....#...##
+...##..##.
+...#.#####
+.#.####.#.
+..#..###.#
+..##.#..#.
+
+Tile 1489:
+##.#.#....
+..##...#..
+.##..##...
+..#...#...
+#####...#.
+#..#.#.#.#
+...#.#.#..
+##.#...##.
+..##.##.##
+###.##.#..
+
+Tile 2473:
+#....####.
+#..#.##...
+#.##..#...
+######.#.#
+.#...#.#.#
+.#########
+.###.#..#.
+########.#
+##...##.#.
+..###.#.#.
+
+Tile 2971:
+..#.#....#
+#...###...
+#.#.###...
+##.##..#..
+.#####..##
+.#..####.#
+#..#.#..#.
+..####.###
+..#.#.###.
+...#.#.#.#
+
+Tile 2729:
+...#.#.#.#
+####.#....
+..#.#.....
+....#..#.#
+.##..##.#.
+.#.####...
+####.#.#..
+##.####...
+##..#.##..
+#.##...##.
+
+Tile 3079:
+#.#.#####.
+.#..######
+..#.......
+######....
+####.#..#.
+.#...#.##.
+#.#####.##
+..#.###...
+..#.......
+..#.###... \ No newline at end of file
diff --git a/2020/Util.hs b/2020/Util.hs
index 7f5f941..7cd674d 100644
--- a/2020/Util.hs
+++ b/2020/Util.hs
@@ -1,5 +1,6 @@
module Util where
+import Data.List
import Data.List.NonEmpty (NonEmpty(..), (<|))
@@ -8,3 +9,6 @@ splitOn _ [] = [] :| []
splitOn f (x:xs) | f x = [] <| splitOn f xs
| otherwise = let l :| ls = splitOn f xs
in (x : l) :| ls
+
+splits' :: [a] -> [(a, [a])]
+splits' l = zip l (zipWith (++) (inits l) (tail (tails l)))