2017-06-19 34 views
4

假设我有记录定义什么是创建记录表单的最短途径?

data Zone = Zone 
    { zId  :: Int -- this zone's ID 
    , zOwnerId :: Int -- the player who owns this zone (-1 otherwise) 
    , zPodsP0 :: Int -- player 0's PODs on this zone 
    , zPodsP1 :: Int -- player 1's PODs on this zone 
    , zPodsP2 :: Int -- player 2's PODs on this zone (always 0 for a two player game) 
    , zPodsP3 :: Int -- player 3's PODs on this zone (always 0 for a two or three player game) 
    } deriving Show 

什么shortways创建从[String]记录从getLine

zones <- replicateM zoneCount $ fmap (mkZone . words) getLine 

读这是我迄今为止做的最好的。

{-# LANGUAGE NamedFieldPuns #-} 

mkZone :: [String] -> Zone 
mkZone xs = Zone {zId, zOwnerId, zPodsP0, zPodsP1, zPodsP2, zPodsP3} 
    where [zId, zOwnerId, zPodsP0, zPodsP1, zPodsP2, zPodsP3] = map read xs 

我使用这个模式很多打codingame bot programmings时,这将是很好,如果有一个更好的方式来做到这一点。

回答

8

RecordWildCards删除了一半的样板。

{-# LANGUAGE RecordWildCards #-} 

mkZone :: [String] -> Zone 
mkZone xs = Zone {..} 
    where [zId, zOwnerId, zPodsP0, zPodsP1, zPodsP2, zPodsP3] = map read xs 
1

你可以用SYB做到这一点,是这样的:

{-# LANGUAGE DeriveDataTypeable #-} 
{-# LANGUAGE ScopedTypeVariables #-} 

import Data.Data 
import Control.Monad.State 

data Zone = Zone { zId, zOwnerId, zPodsP0, zPodsP1, zPodsP2, zPodsP3 :: Int } 
    deriving (Show, Data) 

main = do 
    print (mygread ["1", "2", "3", "4", "5", "6"] :: Maybe Zone) 
    print (mygread ["a", "2", "3", "4", "5", "6"] :: Maybe Zone) 
    print (mygread ["1", "2", "3", "4", "5"] :: Maybe Zone) 

mygread :: forall a . Data a => [String] -> Maybe a 
mygread = evalStateT (fromConstrM read' constr) 
    where 
    constr = head . dataTypeConstrs . dataTypeOf $ (undefined :: a) 
    read' :: forall a . Data a => StateT [String] Maybe a 
    read' = do 
     x:xs <- get 
     put xs 
     lift . fmap fromConstr . readConstr (dataTypeOf (undefined :: a)) $ x 

输出:

Just (Zone {zId = 1, zOwnerId = 2, zPodsP0 = 3, zPodsP1 = 4, zPodsP2 = 5, zPodsP3 = 6}) 
Nothing 
Nothing 

你只需要让你的类型数据(deriving Data)的一个实例。

0

就我个人而言,我会去RecordWildCards并称它为一天。但是,这是另一个有趣的方式,在某些情况下可能会很有用:谨慎风,使用动态类型来获得改变类型的折叠!

{-# LANGUAGE DeriveDataTypeable #-} 

import Data.Dynamic (dynApp, fromDynamic, toDyn) 
import Data.List (foldl') 
import Data.Typeable (Typeable) 

-- Add the 'Typeable' instance to enable runtime type information. 
data Zone = Zone 
    { zId, zOwnerId, zPodsP0, zPodsP1, zPodsP2, zPodsP3 :: Int 
    } deriving (Show, Typeable) 

mkZone :: [String] -> Maybe Zone 
mkZone = fromDynamic . foldl' dynApp (toDyn Zone) . map (toDyn . readInt) 
    where 

    -- This type-specialised 'read' avoids an ambiguous type. 
    readInt :: String -> Int 
    readInt = read 

这将启动类型从Zone构造,:

Int -> Int -> Int -> Int -> Int -> Int -> Zone 

然后相继其应用于每个Int从输入读取,改变它的类型:

Int -> Int -> Int -> Int -> Int -> Zone 
Int -> Int -> Int -> Int -> Zone 
Int -> Int -> Int -> Zone 
Int -> Int -> Zone 
Int -> Zone 
Zone 

而且它的工作原理:

> mkZone ["1", "2", "3", "4", "5", "6"] 
Just (Zone {zId = 1, zOwnerId = 2, zPodsP0 = 3, zPodsP1 = 4, zPodsP2 = 5, zPodsP3 = 6}) 

如果提供的参数太少,你会得到Nothing因为运行时转换失败:

> mkZone ["1", "2", "3", "4", "5"] 
Nothing 

不过,如果你提供太多许多参数,你会得到一个异常:

> mkZone ["1", "2", "3", "4", "5", "6", "7"] 
*** Exception: Type error in dynamic application. 
Can't apply function <<Zone>> to argument <<Int>> 

这是很容易通过使用dynApply而不是dynApp来修复,其返回Maybe而不是抛出。而且只要你在Maybe正在工作,你还不如用Text.Read.readMaybe处理分析错误:

{-# LANGUAGE DeriveDataTypeable #-} 

import Control.Monad ((<=<)) 
import Data.Dynamic (Dynamic, dynApply, fromDynamic, toDyn) 
import Data.List (foldl') 
import Data.Typeable (Typeable) 
import Text.Read (readMaybe) 

data Zone = Zone { … } deriving (Show, Typeable) 

mkZone :: [String] -> Maybe Zone 
mkZone = fromDynamic <=< foldl' go (Just (toDyn Zone)) . map readInt 
    where 

    go :: Maybe Dynamic -> Maybe Int -> Maybe Dynamic 
    go mAcc mx = do 
     acc <- mAcc 
     x <- mx 
     dynApply acc $ toDyn x 

    readInt :: String -> Maybe Int 
    readInt = readMaybe 

真正虽然,可能不这样做。

相关问题