Skip to content

Instantly share code, notes, and snippets.

@nobsun
Last active May 25, 2017 10:10
Show Gist options
  • Save nobsun/9b62bb1fb3c153036c04499f06ef6e08 to your computer and use it in GitHub Desktop.
Save nobsun/9b62bb1fb3c153036c04499f06ef6e08 to your computer and use it in GitHub Desktop.
「ブロックを回す」問題 ref: http://qiita.com/nobsun/items/a48a372dcb1b95199e84
module F05 where
import Control.Arrow (first, (&&&))
import Data.Bool
import Data.List (sortBy,transpose,intercalate,isPrefixOf)
import Data.List.Split (splitOn)
import Data.Ord (comparing)
import Data.Tuple (swap)
rot :: ([String] -> [String], [String] -> [String]) -> [String] -> [String]
rot (trim, extend) = trim . map reverse . transpose . extend
as = ( map (drop 2) . init . tail
, map ("00"++) . ("00000" :) . (++ ["00000"]))
bs = ( map tail . tail
, map ('0' :) . ("00000" :))
count :: [String] -> Int
count = sum . map (length . filter ('1' ==))
rotate :: ([String] -> [String], [String] -> [String]) -> [String] -> String
rotate extr ss = bool "-" (intercalate "/" ss') (ec == ic)
where
ss' = rot extr ss
ec = count ss'
ic = count ss
type Problem = String
type Answer = String
f05 :: Problem -> Answer
f05 p = bool (rotate as) (rotate bs) ("b:" `isPrefixOf` p) (splitOn "/" . drop 2 $ p)
type Test = (Problem, Answer)
{- |
>>> test ( "a:00000/00110/00100/00100/00000", "00000/00000/00000/11100/00100" )
True
>>> test ( "b:00000/00000/00000/00011/00011", "-" )
True
>>> test ( "a:00000/00000/00000/00011/00011", "-" )
True
>>> test ( "b:00000/00000/00100/00000/00000", "00000/00000/01000/00000/00000" )
True
>>> test ( "a:00000/00000/00100/00000/00000", "00000/00000/00000/01000/00000" )
True
>>> test ( "b:00000/00110/00100/00100/00000", "00000/00000/11100/00100/00000" )
True
>>> test ( "b:00000/00000/00011/00011/00000", "00000/00000/00000/11000/11000" )
True
>>> test ( "a:00000/00000/00011/00011/00000", "-" )
True
>>> test ( "a:01110/00100/00000/00000/00000", "00000/00000/00010/00110/00010" )
True
>>> test ( "b:01110/00100/00000/00000/00000", "00000/00010/00110/00010/00000" )
True
>>> test ( "a:00000/11110/00000/00000/00000", "00000/00100/00100/00100/00100" )
True
>>> test ( "b:00000/11110/00000/00000/00000", "00100/00100/00100/00100/00000" )
True
>>> test ( "a:00000/00011/00110/00000/00000", "-" )
True
>>> test ( "b:00000/00011/00110/00000/00000", "00000/00000/01000/01100/00100" )
True
>>> test ( "a:00000/11100/11100/11100/00000", "00000/11100/11100/11100/00000" )
True
>>> test ( "b:00000/11100/11100/11100/00000", "11100/11100/11100/00000/00000" )
True
>>> test ( "a:01000/00000/00101/10010/10001", "-" )
True
>>> test ( "b:01000/00000/00101/10010/10001", "-" )
True
>>> test ( "b:10000/00000/10010/00000/00000", "01010/00000/00000/01000/00000" )
True
>>> test ( "a:10000/00000/10010/00000/00000", "00000/01010/00000/00000/01000" )
True
>>> test ( "a:00000/10101/11010/11010/01000", "-" )
True
>>> test ( "b:00000/10101/11010/11010/01000", "-" )
True
>>> test ( "b:01101/00011/01101/00000/00000", "00000/01010/01010/00100/01110" )
True
>>> test ( "a:01101/00011/01101/00000/00000", "-" )
True
>>> test ( "a:00001/00000/00000/00100/00010", "-" )
True
>>> test ( "b:00001/00000/00000/00100/00010", "-" )
True
>>> test ( "b:00100/00000/00100/01000/00000", "00000/10000/01010/00000/00000" )
True
>>> test ( "a:00100/00000/00100/01000/00000", "00000/00000/10000/01010/00000" )
True
>>> test ( "a:00010/00100/00000/10000/00000", "00000/10000/00000/00100/00010" )
True
>>> test ( "b:00010/00100/00000/10000/00000", "10000/00000/00100/00010/00000" )
True
>>> test ( "b:11010/00011/10101/00001/00001", "-" )
True
>>> test ( "a:11010/00011/10101/00001/00001", "-" )
True
>>> test ( "a:00100/00010/00000/11000/00000", "00000/10000/10000/00010/00100" )
True
>>> test ( "b:00100/00010/00000/11000/00000", "10000/10000/00010/00100/00000" )
True
>>> test ( "b:01010/00000/00000/01000/00000", "00000/10010/00000/00010/00000" )
True
>>> test ( "a:01010/00000/00000/01000/00000", "00000/00000/10010/00000/00010" )
True
>>> test ( "a:00000/00000/00100/10100/00000", "00000/10000/00000/11000/00000" )
True
>>> test ( "b:00000/00000/00100/10100/00000", "10000/00000/11000/00000/00000" )
True
>>> test ( "b:10000/01101/01000/01100/10011", "-" )
True
>>> test ( "a:10000/01101/01000/01100/10011", "-" )
True
>>> test ( "a:00010/00000/00110/01000/10001", "-" )
True
>>> test ( "b:00010/00000/00110/01000/10001", "-" )
True
>>> test ( "b:00000/01000/01100/00000/00000", "00000/01100/01000/00000/00000" )
True
>>> test ( "a:00000/01000/01100/00000/00000", "00000/00000/01100/01000/00000" )
True
>>> test ( "a:01000/00000/00000/10000/00000", "00000/10000/00010/00000/00000" )
True
>>> test ( "b:01000/00000/00000/10000/00000", "10000/00010/00000/00000/00000" )
True
>>> test ( "b:00000/01101/00000/01010/11010", "-" )
True
>>> test ( "a:00000/01101/00000/01010/11010", "-" )
True
>>> test ( "a:00110/00101/00000/10100/00100", "-" )
True
>>> test ( "b:00110/00101/00000/10100/00100", "-" )
True
>>> test ( "b:11000/10110/00000/00110/00000", "00110/00010/10100/10100/00000" )
True
>>> test ( "a:11000/10110/00000/00110/00000", "00000/00110/00010/10100/10100" )
True
>>> test ( "a:00000/00000/00000/00001/00110", "-" )
True
>>> test ( "b:00000/00000/00000/00001/00110", "-" )
True
>>> test ( "b:01011/10001/00000/00000/00000", "00100/00010/00000/00010/00110" )
True
>>> test ( "a:01011/10001/00000/00000/00000", "-" )
True
-}
test :: Test -> Bool
test (p,a) = f05 p == a
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment