第11回 オフラインリアルタイムどう書くで出題された問題の回答です。
会場で書いたそのままです。55分くらいでどうにか。
dokaku.hs
module Main where
import Data.Bits (shift, (.&.))
import Data.List (groupBy)
import Numeric (readHex)
import Test.HUnit (Test(..), runTestTT, (~=?))
type Problem = [Row]
type Row = [(Int, Int)]
type Columns = [Column]
type Column = Int
initState :: Columns
initState = [0..8]
main :: IO ()
main = print =<< runTestTT (TestList $ map toTest testdata)
solve :: String -> String
solve = writeProblem . foldl go initState . readProblem
readProblem :: String -> Problem
readProblem = map toRow . break'
break' :: String -> [String]
break' "" = []
break' s = case break (== '-') s of
(x, '-':y) -> x : break' y
(x, y) -> x : break' y
toRow :: String -> Row
toRow = map (\l -> (fst $ head l, succ $ fst $ last l)) . filter (snd . head) . groupBy (\x y -> snd x == snd y) . zip [0..] . toRow'
toRow' :: String -> [Bool]
toRow' s = map (\m -> (fst (head $ readHex s) .&. m) /= (0 :: Int)) masks
where
masks = map (shift 1) [7,6..0]
go :: Columns -> Row -> Columns
go c r = foldl go' c r
go' :: Columns -> (Int, Int) -> Columns
go' c (x, y) = map f $ zip [0..] c
where
f (i, n) | i == x = c !! y
| i == y = c !! x
| otherwise = n
writeProblem :: Columns -> String
writeProblem = concat . map show
---- unit testing
toTest :: (String, String) -> Test
toTest (input, expected) = expected ~=? solve input
testdata :: [(String, String)]
testdata =
[ ( "d6-7b-e1-9e", "740631825" )
, ( "83-4c-20-10", "123805476" )
, ( "fb-f7-7e-df", "274056813" )
, ( "55-33-0f-ff", "123456780" )
, ( "00-00-00-00", "012345678" )
, ( "00-00-00-55", "021436587" )
, ( "40-10-04-01", "021436587" )
, ( "00-00-aa-00", "103254768" )
, ( "80-20-08-02", "103254768" )
, ( "ff-7e-3c-18", "876543210" )
, ( "aa-55-aa-55", "351708264" )
, ( "55-aa-aa-55", "012345678" )
, ( "db-24-db-e7", "812543670" )
, ( "00-01-00-40", "021345687" )
, ( "00-00-80-00", "102345678" )
, ( "01-40-00-00", "021345687" )
, ( "00-00-00-02", "012345768" )
, ( "00-00-02-00", "012345768" )
, ( "00-14-00-00", "012436578" )
, ( "00-00-01-40", "021345687" )
, ( "00-80-01-00", "102345687" )
, ( "c8-00-00-81", "120354687" )
, ( "05-48-08-14", "021435687" )
, ( "24-05-00-f0", "413205687" )
, ( "40-08-14-01", "021536487" )
, ( "18-c8-80-80", "210534678" )
, ( "1c-88-52-00", "120564738" )
, ( "ec-dc-67-62", "213468705" )
, ( "0a-b6-60-e9", "035162784" )
, ( "52-d6-c6-c2", "120345678" )
, ( "47-e7-b0-36", "231047658" )
, ( "0f-85-91-aa", "108263754" )
, ( "76-b6-ed-f3", "601435782" )
, ( "f5-5e-f7-3d", "025847163" )
, ( "dd-e7-fb-f9", "610247538" )
, ( "8f-f4-af-fd", "583246017" )
, ( "bf-fb-cb-f7", "105382674" )
, ( "e5-fd-ff-ff", "512046378" )
, ( "ef-df-ef-fe", "713205648" )
, ( "bf-7f-fd-d7", "826437105" )
, ( "36-ff-df-de", "814527603" )
, ( "6f-dd-ff-ff", "230685147" )
]