CodinGame/Contests/SmashTheCode/SmashTheCode.hs

228 lines
8.5 KiB
Haskell

{-# LANGUAGE LambdaCase, TupleSections, UnicodeSyntax, Rank2Types #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
module Main (main) where
import Control.Applicative
import Control.Arrow (first, second, (&&&))
import Control.Monad
import Control.Monad.Writer
import Data.Function
import Data.List
import Data.Maybe
import Data.Monoid
import Data.Array (Array, (!), (//))
import System.IO
--import System.Time
import System.Timeout
import System.CPUTime
import Debug.Trace
import qualified Data.Array as A
{-# ANN module "HLint: ignore Use if" #-}
{-# ANN module "HLint: ignore Eta reduce" #-}
{-# ANN module "HLint: ignore Redundant $" #-}
{-# ANN module "HLint: ignore Redundant do" #-}
type Color = Int
type Rotation = Int
type Block = (Color, Color)
type Column = Int
type Row = Int
data Cell = Empty | Skull | Color Color deriving (Eq, Ord, Show)
type Grid = Array (Column, Row) Cell
main IO ()
main = do
hSetBuffering stdout NoBuffering -- DO NOT REMOVE
forever $ do
blocks replicateM 8 getBlock
--start ← getClockTime
myGrid getGrid
opGrid getGrid
--let traceLength xs = traceShow (length xs) xs
let limiter xs = {-traceLength <$>-} evaluateListWithTimeout 88000 xs
(col, rot) step limiter blocks myGrid
--end ← col `seq` rot `seq` getClockTime
--let ms = round ((end `diffSeconds` start) * 1000)
--hPutStrLn stderr $ show ms ++ "ms"
putStrLn $ unwords [show col, show rot]
getBlock IO Block
getBlock = do
[colorA, colorB] map read . words <$> getLine
pure (colorA, colorB)
getGrid IO Grid
getGrid = fmap (A.array ((0,0),(5,11)) . concat) $
forM [0..11] $ \row do
line getLine
pure [ ((col, row), cell ch) | (col, ch) zip [0..] line ]
where
cell '.' = Empty
cell '0' = Skull
cell ch = Color (read [ch])
newtype Candidates = Candidates [(Int, ((Column, Rotation), Candidates))]
step Functor f (a. [a] f [a]) [Block] Grid f (Column, Rotation)
step limiter blocks myGrid = select <$> limiter stream
where
Candidates start = candidates blocks myGrid
stream = concatMap snd . drop 1 . takeWhile (not . null . snd)
. iterate deepen . (0,)
. take 40 . sortBy (flip compare `on` fst)
$ start
deepen (depth, cs0) =
{- trace (show depth ++ " " ++ show (fst (head cs))) $ -}
(depth+1, cs')
where
cs = sortBy (flip compare `on` fst) cs0
cs' = map (first (`div` (depth + 3)))
. take 40 . sortBy (flip compare `on` fst)
$ concatMap (\k mapMaybe (candidate k) cs) [0..6]
candidate n c@(_, (_, Candidates cs)) = listToMaybe (drop n cs)
select [] = (0, 0)
select cs = fst $ snd $ maximumBy (compare `on` fst) cs
candidates [Block] Grid Candidates
candidates [] _ = Candidates []
candidates (block:blocks) grid0 = Candidates cs
where
try col rot = do
(grid1, points1) simulate grid0 block col rot
let score1 = score grid1 points1
let Candidates cs1 = candidates blocks grid1
let adjust (score2, (mv2, Candidates cs2)) =
let scoreAvg = (2 * score1 + 3 * score2) `div` 5
in (score1 + score2, ((col, rot), Candidates (map adjust cs2)))
pure $! score1 `seq` (score1, ((col, rot), Candidates (map adjust cs1)))
hint = uncurry (+) block `div` 2
columns = filter (\c c >= 0 && c <= 5) $ map (hint +) [0,-1,1,-2,2,-3,3,-4,4,-5,5]
rotations = [1,0,3,2]
cs = catMaybes $ try <$> columns <*> rotations
score Grid Int Int
score grid points = 100 * points + 10 * matches + emptyNeighbours
where
matches = sum . map (^2) . filter (> 1) . map length $ colorGroups
colorCells = filter (isColor . snd) $ A.assocs grid
colorGroups = connectedGroups adjacentMatch colorCells
neighbours (c,r) = map (id &&& (grid!))
$ filter (A.inRange (A.bounds grid))
$ [(c-1,r), (c+1,r), (c,r-1), (c,r+1)]
supported (c,r) = any (\n r+n > 11 || grid!(c,r+n) /= Empty) [0..3]
emptyNeighbours = flip count colorCells $
any (\(p,v) v == Empty && supported p) . neighbours . fst
count (a Bool) [a] Int
count p xs = length (filter p xs)
simulate Grid Block Column Rotation Maybe (Grid, Int)
simulate grid (colorA, colorB) col rot
| not (A.inRange (A.bounds grid) crA) ||
not (A.inRange (A.bounds grid) crB) ||
grid!crA /= Empty || grid!crB /= Empty = Nothing
| otherwise = Just . second getSum . runWriter $ simFall startGrid 1
where
(crA, crB) = case rot of
0 ((col,0), (col+1,0))
1 ((col,1), (col, 0))
2 ((col,0), (col-1,0))
3 ((col,0), (col, 1))
startGrid = grid // [ (crB, Color colorB), (crA, Color colorA) ]
{-
addSkulls ∷ Int → Grid → Grid
addSkulls nskulls grid = newGrid
where
packColumn c = zipWith (\r x → ((c,r),x)) [11,10..0]
$ (++ repeat Empty)
$ (++ replicate nskulls Skull)
$ takeWhile (/= Empty)
$ map (\r → grid!(c,r)) [11,10..0]
newGrid = A.array ((0,0),(5,11)) $ concatMap packColumn [0..5]
-}
simFall (Applicative m, MonadWriter (Sum Int) m) Grid Int m Grid
simFall grid = simDisappear newGrid
where
packColumn c = zipWith (\r x ((c,r),x)) [11,10..0]
$ (++ repeat Empty)
$ filter (/= Empty)
$ map (\r grid!(c,r)) [11,10..0]
newGrid = A.array ((0,0),(5,11)) $ concatMap packColumn [0..5]
simDisappear (Applicative m, MonadWriter (Sum Int) m) Grid Int m Grid
simDisappear grid stage = case null erased of
True pure grid
False do
tell . Sum $ 10 * blocksCleared * scale
simFall erasedGrid (stage + 1)
where
colorCells = filter (isColor . snd) $ A.assocs grid
skullCells = filter ((== Skull) . snd) $ A.assocs grid
groups = connectedGroups adjacentMatch colorCells
largeGroups = filter ((>= 4) . length) groups
erasedColors = concat largeGroups
erasedSkulls = filter (\(cr,_) any (adjacent cr . fst) erasedColors) skullCells
erased = erasedColors ++ erasedSkulls
erasedGrid = grid // map (second (const Empty)) erased
blocksCleared = length erasedColors
chainPower = if stage < 2 then 0 else 8 * 2^(stage-2)
uniqueColors = length . nub $ map snd erasedColors
colorBonus = if uniqueColors < 2 then 0 else 2^(uniqueColors-1)
groupBonus = sum (map (perGroupBonus . length) largeGroups)
perGroupBonus n = if n >= 11 then 8 else n - 4
scale = max 1 $ min 999 $ chainPower + colorBonus + groupBonus
isColor Cell Bool
isColor Empty = False
isColor Skull = False
isColor (Color _) = True
adjacent (Column,Row) (Column,Row) Bool
adjacent (c1,r1) (c2,r2) = (c1 == c2 && (r1 == r2 - 1 || r1 == r2 + 1)) ||
(r1 == r2 && (c1 == c2 - 1 || c1 == c2 + 1))
adjacentMatch ((Column, Row), Cell) ((Column, Row), Cell) Bool
adjacentMatch (cr1,x1) (cr2,x2) = x1 == x2 && adjacent cr1 cr2
connectedGroups (a a Bool) [a] [[a]]
connectedGroups p rem = case rem of
[] []
(x:rem')
let go fringe others = case fringe of
[] ([], others)
(y:fringe')
let (adj, notAdj) = partition (p y) others
in first (y:) $ go (fringe' ++ adj) notAdj
(conn, notConn) = go [x] rem'
in conn : connectedGroups p notConn
{-
diffSeconds ∷ ClockTime → ClockTime → Double
diffSeconds (TOD s' p') (TOD s p) =
fromIntegral ((s' - s) * 1000000000000 + (p' - p)) / 1e12
-}
-- Compute elements of the list to WHNF for `t` microseconds. After
-- `t` microseconds, abandon the calculation and terminate the list.
evaluateListWithTimeout Integer [a] IO [a]
evaluateListWithTimeout t xs = do
end (+) <$> getCPUTime <*> pure (1000000 * t)
flip fix xs $ \loop xs do
now getCPUTime
r timeout (fromIntegral $ max 0 (end - now) `div` 1000000) $
case xs of
[] pure []
(a:as) pure $! a `seq` (a:as)
case r of
Nothing pure []
Just [] pure []
Just (a:as) (a:) <$> loop as