LoginSignup
1
1

More than 5 years have passed since last update.

第一回 オフラインリアルタイムどう書く

Posted at

第一回 オフラインリアルタイムどう書くという勉強会があったそうです。
残念ながら僕は参加できなかったんですが、当日のお題をHaskellで解いてみました。
なるべくシンプルに実装したつもりです。

toukaku.hs
module Main where

import Data.List (transpose, insert)

data Cell   = O | X | None deriving (Eq, Show, Ord, Enum)
type Board  = [Cell]
data Result = OWon | XWon | FoulOWon | FoulXWon | Draw deriving Enum

instance Show Result where
  show OWon     = "o won."
  show XWon     = "x won."
  show FoulOWon = "Foul: o won."
  show FoulXWon = "Foul: x won."
  show Draw     = "Draw game."

main :: IO ()
main = mapM_ (print . judge) . lines =<< getContents

judge :: String -> Result
judge = judge' O (replicate 9 None) . take 9 . map (subtract 49 . fromEnum)

judge' :: Cell -> Board -> [Int] -> Result
judge' _ _ []     = Draw
judge' c b (i:is) = case put c i b of
  Nothing -> toEnum (3 - fromEnum c)
  Just b' -> if win c b'
    then toEnum $ fromEnum c
    else judge' (toEnum (1 - fromEnum c)) b' is

win :: Cell -> Board -> Bool
win c b = any (all (== c)) $ mat ++ transpose mat ++ map (zipWith (!!) mat) [[0,1,2], [2,1,0]]
  where
    mat = take 3 . map (take 3) $ iterate (drop 3) b

put :: Cell -> Int -> Board -> Maybe Board
put c n b = case b !! n of
  None -> Just . map snd . insert (n, c) . filter ((/= n) . fst) $ zip [0..] b
  _    -> Nothing
1
1
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
1
1