Skip to content

Instantly share code, notes, and snippets.

Show Gist options
  • Save vigdorchik/5379e0d094f93822dacfa221be85971a to your computer and use it in GitHub Desktop.
Save vigdorchik/5379e0d094f93822dacfa221be85971a to your computer and use it in GitHub Desktop.
import Data.List
import Data.Int
import Data.Bits
import System.IO
type Bitmap = Int64
data Problem = Problem Int {-rows-} Int {-cols-} Bitmap {-board-} [Bitmap] {-tiles-}
extract :: [String] -> [Problem]
extract ls =
let groups c = takeWhile (not . null) . unfoldr (Just . break ((== c) . last)
. dropPatt) where
dropPatt (s:tl)| c == last s = tl
dropPatt x = x
texts = groups '=' ls in
map (single . groups ':') texts where
single :: [[[Char]]] -> Problem
single (board:tiles) =
let m = length board; n = length (head board)
toBitmap charss = foldr1 (.|.) [if c =='1' then bit (i*n+j) else 0|
(row, i) <- zip charss [0..],
(c, j) <- zip row [0..]] in
Problem m n (toBitmap board) (map toBitmap tiles)
solve :: Problem -> [(Int, Int)]
solve (Problem m n board tiles) =
let combine tile run =
[(curr .|. shifted, (i,j):coords)| (curr, coords) <- run,
i <- [0..m-1], j <- [0..n-1], let shifted = shiftL tile (i*n+j),
shifted .&. board == shifted && shifted .&. curr == 0]
varz = foldr combine [(0,[])] tiles
Just (_,coords) = find ((==) board . fst) varz in
coords
main = do
f <- openFile "./input.dat" ReadMode
problems <- fmap (extract . filter (not . null) . lines) $ hGetContents f
putStrLn . unlines . map (intercalate ", " . map show . solve) $ problems
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment