Skip to content

Instantly share code, notes, and snippets.

@mattsan
Created November 13, 2012 14:13
Show Gist options
  • Save mattsan/4065963 to your computer and use it in GitHub Desktop.
Save mattsan/4065963 to your computer and use it in GitHub Desktop.
第五回オフラインリアルタイムどう書くの回答例(Haskell) ref: http://qiita.com/items/4a1b341f45ebf1d05fc1
module Answer(solve, input_cards) where
import Data.List
rank '3' = 1
rank '4' = 2
rank '5' = 3
rank '6' = 4
rank '7' = 5
rank '8' = 6
rank '9' = 7
rank 'T' = 8
rank 'J' = 9
rank 'Q' = 10
rank 'K' = 11
rank 'A' = 12
rank '2' = 13
rank 'o' = 14
rank_char n = "-3456789TJQKA2o" !! n
join_string _ [] = "-"
join_string d ws = foldr1 (\w s -> w ++ d:s) ws
join_string' [] = ""
join_string' ws = foldr1 (\w s -> w ++ s) ws
combination n = filter (\x -> length x == n) . subsequences
rank_of_list [(_,r)] = r
rank_of_list ((_,r):xs)
| r1 == rank 'o' = r
| r == rank 'o' = r1
| r == r1 = r
| otherwise = 0
where
r1 = rank_of_list xs
input_cards [] = []
input_cards "-" = []
input_cards (s:r:xs) = (s, rank r):(input_cards xs)
input (',':xs) = ([], input_cards xs)
input (s:r:xs) = let (fs, hs) = input xs in ((s, rank r):fs, hs)
solve xs = join_string ',' $ map (\xs -> join_string' xs) $ map (\xs -> map (\(s,r) -> [s, rank_char r]) xs) $ filter (\hs -> fr < (rank_of_list hs)) hss
where
(fs, hs) = input xs
fr = rank_of_list fs
hss = combination (length fs) hs
module Main where
import Data.List
import Test.HUnit
import Answer
split :: (a -> Bool) -> [a] -> [[a]]
split f s =
case dropWhile f s of
[] -> []
s' -> w : split f s''
where (w, s'') = break f s'
doAssert :: [String] -> Assertion
doAssert (name:input:expected:_) = assertEqual name e a
where
e = sort $ map (\x -> sort $ input_cards x) $ split (== ',') $ expected
a = sort $ map (\x -> sort $ input_cards x) $ split (== ',') $ solve input
doAssert _ = error "Specify a list which contains more than 3 items."
main :: IO ()
main =
readFile "patterns.tsv"
>>= runTestTT . test . map (doAssert . split (== '\t')) . lines
>> return ()
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment