হাস্কেল - 1493 বাইট
এই সংস্করণে, কোনও বিশদ ত্রুটির বার্তা নেই এবং আউটপুটটি অনেক বেশি বেসিক। প্রধান পরিবর্তন প্রতিস্থাপন করা হয়েছিল Either String aসঙ্গে Maybe aএবং যেহেতু তারা উভয় monads, এই কেবল সোয়াপিং দ্বারা acheived ছিল Right aসঙ্গে Just aএবং Left Stringসঙ্গে Nothing।
{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding ((>>=),concatMap,filter,foldl,head,last,map,null,replicate)
import Control.Applicative hiding (empty)
import Control.Monad hiding (replicateM)
import Data.Vector hiding ((++),concat,foldM,reverse,zip)
main=getLine>>= \s->h$t<$>(zip$cycle[w,v])<$>b s>>= \m->u(\b(c,x)->case d b x c of r@(Just _)->r;Nothing->if not$null$findIndices(\y->e$d b y c)$t[(x,y)|x<-[0..7],y<-[0..7]];then é;else d b x$not c)k$n m
where b(x:y:s)=(:)(read [x],read [y])<$>b s;b(_:_)=é;b[]=è[];d b z c=let d=join$m(f b z c)$m(\v->(head v,last v))$replicateM 2$t[-1,0,1];in if null d;then Nothing;else u(\b (x,y)->case b!?y of Just r->(case r!?x of Just _->è$b//[(y,r//[(x,è c)])];Nothing->é);Nothing->é)b$n$d`snoc`z;e(Nothing)=w;e(Just _)=v;f b(x,y)c z@(u,v)=let r=x+u;s=y+v;t=(r,s);in (case g b t of Just(Just d)->if d==c;then l;else (case g b (r+u,s+v) of Just(Just _)->t`cons`f b t c z;_->l);Just(Nothing)->l;Nothing->l);g b(x,y)=(case b!?y of Just col->col!?x;Nothing->é);h(Just b)=p$(o$n$m(\r->o(n$m(\c->case c of Just False->"B";Just True->"W";Nothing->".")r)++"\n")b)++i(q(\(w,b)(rw,rb)->(w+rw,b+rb))(0,0)$m(\r->q(\s@(w,b)c->case c of Just True->(w+1,b);Just False->(w,b+1);_->s)(0,0)r)b);h Nothing=p"e";i(w,b)|w>b="W"++s w|b>w="B"++s b|v="N"++s(w+b);j=r 8 é;k=r 8 j//[(3,j//[(3,è v),(4,è w)]),(4,j//[(3,è w),(4,è v)])];l=empty;m=map;n=toList;o=concat;p=putStrLn;q=foldl;r=replicate;s=show;t=fromList;u=foldM;v=True;w=False;é=Nothing;è=Just
$ printf "232425140504032627" | ./nano-rve
........
........
........
B.BBB...
BBBWW...
B.B.....
..B.....
..B.....
B11
আসল সংস্করণ - 4533 বাইট
আমি যখন গল্ফ করব তখন প্রতিযোগিতা হবে!
সম্পাদনা এটি এসে গেছে
{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding ((>>=),concatMap,filter,foldl,map,null,replicate)
import Control.Applicative hiding (empty)
import Control.Monad
import Data.Either
import Data.Vector hiding ((++),concat,foldM,reverse,zip)
type Case = Maybe Bool
type Board = Vector (Vector Case)
type Coord = (Int,Int)
-- fmap (toList) $ replicateM 2 [-1,0,1] -- minus (0,0)
directions :: Vector Coord
directions = fromList [(-1,-1),(-1,0),(-1,1),(0,-1),(0,1),(1,-1),(1,0),(1,1)]
-- [(x,y) | x <- [0..7], y <- [0..7]]
allCoords :: Vector Coord
allCoords = fromList [(0,0),(0,1),(0,2),(0,3),(0,4),(0,5),(0,6),(0,7),(1,0),(1,1),(1,2),(1,3),(1,4),(1,5),(1,6),(1,7),(2,0),(2,1),(2,2),(2,3),(2,4),(2,5),(2,6),(2,7),(3,0),(3,1),(3,2),(3,3),(3,4),(3,5),(3,6),(3,7),(4,0),(4,1),(4,2),(4,3),(4,4),(4,5),(4,6),(4,7),(5,0),(5,1),(5,2),(5,3),(5,4),(5,5),(5,6),(5,7),(6,0),(6,1),(6,2),(6,3),(6,4),(6,5),(6,6),(6,7),(7,0),(7,1),(7,2),(7,3),(7,4),(7,5),(7,6),(7,7)]
initBoard :: Board
initBoard = vs // [(3,v1),(4,v2)]
where va = replicate 8 Nothing
v1 = va // [(3,Just True),(4,Just False)]
v2 = va // [(3,Just False),(4,Just True)]
vs = replicate 8 va
showBoard :: Board -> String
showBoard b = (concat $ toList $ map (showRow) b) ++ (showScore b)
where showCase :: Case -> String
showCase c = case c of
Just False -> "░B"
Just True -> "▓W"
Nothing -> "██"
showRow :: Vector Case -> String
showRow r = concat (toList $ map (showCase) r) ++ "\n"
showScore :: Board -> String
showScore b = winner score ++ "\n"
where scoreCase :: (Int,Int) -> (Maybe Bool) -> (Int,Int)
scoreCase (w,b) (Just True) = (w+1,b)
scoreCase (w,b) (Just False) = (w,b+1)
scoreCase s _ = s
scoreRow :: Vector Case -> (Int,Int)
scoreRow r = foldl (scoreCase) (0,0) r
score :: (Int,Int)
score = foldl (\(w,b) (rw,rb) -> (w+rw,b+rb)) (0,0) $ map (scoreRow) b
winner :: (Int,Int) -> String
winner (w,b) | w > b = "White with " ++ show w ++ " against Black with " ++ show b ++ "."
| b > w = "Black with " ++ show b ++ " against White with " ++ show w ++ "."
| otherwise = "Nobody with " ++ show (w+b) ++ "."
printBoard :: Board -> IO ()
printBoard b = putStrLn $ showBoard b
pm :: Either String Board -> IO ()
pm (Right b) = printBoard b
pm (Left s) = putStrLn s
lookupBoard :: Board -> Coord -> Either String Case
lookupBoard b (x,y) = case b !? y of
Just col -> case col !? x of
Just c -> Right c
Nothing -> Left "x is out of bounds"
Nothing -> Left "y is out of bounds"
updateBoard :: Board -> Coord -> Bool -> Either String Board
updateBoard b (x,y) c = case b !? y of
Just r -> case r !? x of
Just _ -> Right $ b // [(y,r // [(x,Just c)])]
Nothing -> Left "x is out of bounds"
Nothing -> Left "y is out of bounds"
makePath :: Board -> Coord -> Bool -> Coord -> Vector Coord
makePath b (x,y) c (px,py) = case lookupBoard b (nx,ny) of
Right (Just pc) -> if pc == c
then empty
else case lookupBoard b (nx+px,ny+py) of
Right (Just _) -> (nx,ny) `cons` makePath b (nx,ny) c (px,py)
_ -> empty
Right (Nothing) -> empty
Left _ -> empty
where nx = x+px
ny = y+py
makeMove :: Board -> Coord -> Bool -> Either String Board
makeMove b xy@(x,y) c = if null cases
then Left $ "impossible move " ++ show xy ++ "."
else foldM (\ob (cx,cy) -> updateBoard ob (cx,cy) c) b $ toList $ cases `snoc` (x,y)
where cases = join $ map (makePath b (x,y) c) directions
makeMoves :: Board -> Vector (Bool,Coord) -> Either String Board
makeMoves b ms = foldM (\ob (c,xy) -> case makeMove ob xy c of
rb@(Right _) -> rb
Left _ -> if not $ null $ findIndices (\xy -> isRight $ makeMove ob xy c) allCoords
then Left $ "wrong move " ++ show xy ++ "."
else makeMove ob xy (not c)) b $ toList ms
movesFromString :: String -> Either String (Vector (Bool,Coord))
movesFromString cs = fromList <$> (zip $ cycle [False,True]) <$> coords cs
where coords (x:y:cs) = (:) (read [x],read [y]) <$> coords cs
coords (_:cs) = Left "invalid coordinates string"
coords [] = Right []
isRight :: Either a b -> Bool
isRight (Left _) = False
isRight (Right _) = True
main=getLine>>= \s->pm$movesFromString s>>=makeMoves initBoard
দ্রষ্টব্য: আপনার দ্বিতীয় উদাহরণটি 2324251 4 0504032627 হওয়া উচিত ।
টেস্ট
স্ক্রিনশট সহ চোখের জ্বালা রোধ করতে।
$ printf "232425140504032627" | ./rve

$ printf "2324" | ./rve

$ printf "1" | ./rve
invalid coordinates string
$ printf "24" | ./rve
wrong move (2,4).
পেতে করা সম্ভব impossible move (x,y)যখন আপনি (প্রোগ্রামের নাড়িভুঁড়ি থেকে এবং আপনার ব্যবহার করা উচিত নয় যে ফাংশন) এবং innardics ব্যবহার x/y is out of bounds।