问题 强制模式顺序


我正在Haskell写一个Magic The Gathering(MTG)游戏引擎。

对于那些不熟悉MTG的人来说,它是一种纸牌游戏,其中卡片最多可以有5种颜色:白色(W),蓝色(U),黑色(B),红色(R)和绿色(G)。

{-# LANGUAGE ViewPatterns #-}
import Data.Set

data Color = W | U | B | R | G
    deriving (Show, Eq, Ord)

data Card = Card (Set Color) -- simplified Card type with only its colors

viewColors :: Card -> [Color]
viewColors (Card colors) = toList colors

我想做的是像这样的颜色模式匹配:

foo :: Card -> String
foo (viewColors -> [W, B]) = "card is white and black"
foo _ = "whatever"

到现在为止还挺好。但这里有一个问题:我可以在视图模式中错误地键入颜色顺序,如下所示:

bar :: Card -> String
bar (viewColors -> [B, W]) = "this will never get hit"
bar _ = "whatever"

当然,我本来可以写的 viewColors 以一种直接解决此问题的方式。或者我可以使用警卫,但我不愿意。这有几种方法可以做到这一点

viewColors :: Card -> (Bool, Bool, Bool, Bool, Bool)
viewColors (Card colors) = let m = (`member` colors)
    in (m W, m U, m B, m R, m G)

这种解决方案在模式匹配时过于冗长,即使我使用的是同构类型 Bool 但标识符较短(和/或有意义)。匹配绿卡看起来像

baz :: Card -> String
baz (viewColors -> (False, False, False, False, True)) = "it's green"

data ColorView = W | WU | WUB | ... all combos here

viewColors :: Card -> ColorView
viewColors (Card colors) = extract correct Colorview from colors

该解决方案具有组合爆炸。实现起来非常糟糕,但很好用,特别是如果我有一个 colorViewToList :: ColorView -> [Color] 在模式匹配后允许编程提取。


我不知道以下是否可以在Haskell中近似,但以下是理想的:

fuz :: Card -> String
fuz (viewColors -> (W :* ())) = "it's white"
fuz (viewColors -> (W :* U :* ())) = "it's white and blue"
fuz (viewColors -> (W :* B :* ())) = "it's white and black"

我愿意使用高级语言扩展来允许这种代码:DataKinds,PolyKinds,TypeFamilies,MultiParamTypeClasses,GADT,你可以命名它。

这样的事情可能吗?你有其他建议的方法吗?


4368
2017-09-24 19:03


起源

为什么不使用警卫?一个守卫几乎和视图模式一样漂亮: f card | card color` [B,W] = ... |卡 color [B,U,W] = ......`。而且,这听起来像一个很酷的项目;你打算用它做什么? - Tikhon Jelvis
你可能想检查一下 这个 出。 - Paul Visschers
@TikhonJelvis:我对卫兵不过敏......他们干净又容易。只是我喜欢模式匹配更多。此外,学习理论本身也很有趣。 - Thomas Eding
@PaulVisschers:感谢您的链接。前几天谷歌搜索“Haskell mtg”时,我惊讶地发现了同样的链接。绝对是我想浏览的东西,不过我相信我会对我的引擎采用一种截然不同的方法(其他开源Magic程序也是如此)。 - Thomas Eding
OverloadedLists 会有所帮助。


答案:


我喜欢录制解决方案,但是使用类型类很容易

{-# LANGUAGE ViewPatterns, ScopedTypeVariables #-}

import qualified Data.Set as Set

data Color = W' | U' | B' | R' | G' deriving (Show, Eq, Ord)
data Card = Card (Set.Set Color) 

newtype W a = W a
newtype U a = U a
newtype B a = B a
newtype R a = R a
newtype G a = G a

class ToColors x where
  toColors :: x -> [Color]
  reify :: x

instance ToColors () where
  toColors _ = []
  reify = ()

instance ToColors a => ToColors (W a) where
  toColors (W a) = W':toColors a
  reify = W reify

--other instances

members :: Set.Set Color -> [Color] -> Bool
members s = foldl (\b e -> b && (Set.member e s)) True

viewColors :: forall a. ToColors a => Card -> Maybe a
viewColors (Card s) = let a = reify :: a in 
  if members s (toColors a) then (Just a) else Nothing

foo :: Card -> String
foo (viewColors -> Just (W (B ()))) = "card is white and black"
foo _ = "whatever"

这很容易被重新设计以获得其他语法。比如,您可以将颜色定义为不带参数的类型,然后使用中缀异构列表构造函数。无论哪种方式,它都不关心订单。

编辑:如果你想匹配简单的精确集合 - 只需替换 members 功能如此

viewColors :: forall a. ToColors a => Card -> Maybe a
viewColors (Card s) = let a = reify :: a in 
  if s == (Set.fromList . toColors $ a) then (Just a) else Nothing

3
2017-09-24 22:23



太棒了,这完全满足了我的需求。也就是说,完全不需要ScopedTypeVariables来编译它;)(至少如果没有禁用单态限制。) - Thomas Eding
@ThomasEding。我应该想到这一点。即使使用,你也可以使用它进行类型检查 NoMonomorphismRestriction 如果你使用抽象而不是 let 避免泛化 viewColors (Card s) = flip ($) reify (\a -> if s == (Set.fromList . toColors $ a) then (Just a) else Nothing) 有感染类型 viewColors :: ToColors a => Card -> Maybe a 这正是你想要的 - Philip JF
@ThomasEding此解决方案与“记录解决方案”具有相同的功能。 Just (W (B ()))) 既是 [W',B',U'] 和 [W',B'], 但不是 [W'] - wit
@wit编辑提供完全匹配。所以不行。 - Philip JF


主要问题是你希望有一个排列而不是单个值 view。我们只有一种允许排列的类型 - 记录。

所以,我们可以添加新数据,记录类型

data B = F|T -- just shorter name for Bool in patterns
data Palette = P {isW, isU, isB, isR, isG :: B}

bool2b :: Bool -> B
bool2b True  = T
bool2b False = F

viewColors :: Card -> Palette
viewColors (Card colors) = let m = bool2b . (`member` colors)
    in P {isW = m W, isU = m U, isB = m B, isR = m R, isG = m G}

foo :: Card -> String
foo (viewColors -> P {isW=T, isB=T}) = "card is white and black"
foo _ = "whatever"

更新

我们也可以 拒绝 错误的模式。但是这个解决方案更难看,但它允许使用“经典”模式

{-# LANGUAGE GADTs #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE RankNTypes #-}
data Color = W | U | B | R | G  deriving (Eq)

data W' 
data U' 
data B'
data R'
data G'

data Color' a where
      W' :: Color' W'
      U' :: Color' U'
      B' :: Color' B'
      R' :: Color' R'
      G' :: Color' G'

data M a = N | J a -- just shorter name for Maybe a in patterns

data Palette = Palette 
      (M (Color' W')) 
      (M (Color' U')) 
      (M (Color' B')) 
      (M (Color' R')) 
      (M (Color' G'))

并定义 viewColor

viewColors :: Card -> Palette
viewColors (Card colors) = 
  let 
    m :: Color -> Color' a -> M (Color' a)
    m c e = if c `member` colors then J e else N
  in P (m W W') (m U U') (m B B') (m R R') (m G G')

foo :: Card -> String
foo (viewColors -> Palette (J W') N (J B') N N) = 
      "card is white and black"
foo _ = "whatever"

4
2017-09-24 21:48



不错的解决方案,但有没有办法让它与颜色WUB不匹配的卡 foo (viewColors -> P { isW=T })?无论如何,这对于至少查询卡片颜色的一部分是有用的。 - Thomas Eding
@ThomasEding,添加也否认错误的模式 - wit


编辑:进一步的测试表明,该解决方案实际上并不起作用。


你实际上不需要任何更多的扩展,我想出了一个可以做你想要的解决方案,但你可能想要优化它,重命名一些东西,并使它变得不那么难看。您只需要创建一个新的数据类型并实现 Eq 你自己并让操作员使用 infixr

{-# LANGUAGE ViewPatterns #-}
import Data.Set

data Color = W | U | B | R | G
    deriving (Show, Eq, Ord)

data Card = Card (Set Color) -- simplified Card type with only its colors

-- you may need to fiddle with the precedence here
infixr 0 :*
data MyList a = END | a :* (MyList a) deriving (Show)

myFromList :: [a] -> MyList a
myFromList [] = END
myFromList (x:xs) = x :* myFromList xs

instance Eq a => Eq (MyList a) where
    END == END = True
    END == _   = False
    _   == END = False
    l1  == l2  = allElem l1 l2 && allElem l2 l1
        where
            -- optimize this, otherwise it'll just be really slow
            -- I was just too lazy to write it correctly
            elemMyList :: Eq a => a -> MyList a -> Bool
            elemMyList a ml = case ml of
                END -> False
                (h :* rest) -> if a == h then True else elemMyList a rest
            allElem :: Eq a => MyList a -> MyList a -> Bool
            allElem END l = True
            allElem (h :* rest) l = h `elemMyList` l && allElem rest l

viewColors :: Card -> MyList Color
viewColors (Card colors) = myFromList $ toList colors

fuz :: Card -> String
fuz (viewColors -> (W :* END)) = "it's white"
fuz (viewColors -> (W :* U :* END)) = "it's white and blue"
fuz (viewColors -> (W :* B :* END)) = "it's white and black"
fuz (viewColors -> (W :* B :* R :* END)) = "it's white, black, and red"
fuz (viewColors -> (W :* U :* B :* R :* G :* END)) = "it's all colors"
fuz _ = "I don't know all my colors"

main = do
    putStrLn $ fuz $ Card $ fromList [W, B]
    putStrLn $ fuz $ Card $ fromList [B, W]

编辑:刚刚修改了一下代码


2
2017-09-24 19:48



另一个类似的解决方案是转换每个 MyList a 成 [a]排序,然后只是使用 ==。这可能是更容易阅读的代码行。但是,我写得很快,所以有明确的改进空间。 - bheklilr
此解决方案也不完全正常。例如,如果我将WU案例写为 (U :* W :* END) 并改变 main 卡片的颜色 [W, U] 和 [U, W] 对于两者,我得到“我不知道我的所有颜色”。也就是说,你的评论激励我为比赛写一个视图模式,我很高兴: fuz (matchColors [W, U] -> True) = blah 哪里 matchColors 无论书面顺序如何,都可以按摩输入。 - Thomas Eding
@ThomasEding嗯,很奇怪,我只是说我很快就编写了这段代码并没有用它做太多测试,但基础知识可以得到你想要的东西。但是,如果你只是想使用 matchColors,那么你也可以只使用警卫,这也是更干净的代码。 - bheklilr
是啊。比任何事情更多或好奇。我可能最终会做明显的(警卫),但我仍然会修补我原来的问题来学习新的东西。 - Thomas Eding
我不太了解 ViewPatterns,所以我检查了输出 ghc --make -ddump-simpl code.hs 并且很快就看到它将它转换为与case语句匹配的模式,所以我认为它甚至不会像你喜欢它那样工作。你可以试着多玩一下,但我不认为你想要的是真的可能。看来我之前的测试可能只是一个侥幸,因为它没有使用 Eq 实例。 - bheklilr


我认为你应该专注于准确地表达卡片的颜色,然后担心其他问题,比如稍后简化。这听起来像你的 Bool 元组解决方案几乎是完美的,但我猜这张卡片 必须 有一种颜色,对吗?

在这种情况下,这样的东西可能会起作用,并且很容易进行模式匹配:

data CardColors = W' BlackBool GreenBool ...
                | B' WhiteBool GreenBool ...
                | G' BlackBool WhiteBool ...
                ....

data BlackBool = B 
               | NotB
-- etc.

您可以非常轻松地创建具有已定义顺序的异构列表,但我不认为这种多态将在此为您服务。


0
2017-09-24 20:16



Magic允许卡片无色。无论我原来问题的实用性如何,我仍然会着迷于一种工作技术,只是为了了解它是如何完成的。虽然现在我认为某种类型类的编写方式类似于Haskell中类型安全的printf如何工作,尽管我今天无法尝试这样的代码。 - Thomas Eding


(不是你问题的答案,但希望能解决你的问题!)

我会选择可能有效的最蠢的事情:

is :: Card -> Color -> Bool
is card col = col `elem` (viewColors card) -- can be optimized to use the proper elem!

接着

foo :: Card -> String
foo c
    | c `is` B && c `is` W = "card is black and white"
    | c `is` R || c `is` G = "card is red or green"
    | otherwise = "whatever"

如果拼出整个列表来检查一张卡片是否有全部5种颜色太长,那么你可以定义额外的组合器

hasColors :: Card -> [Color] -> Bool
hasColors card = all (`elem` (viewColors card))

这是不可接受的吗?


0
2017-09-25 11:40



我不使用守卫的主要原因通常是我更喜欢案例表达而不是多个定义的模式匹配。在这些情况下使用警卫很烦人(没有双关语意)我认为写作 case () of _ | x == 1 -> 1; _ | x == 2 -> 2 ; ... 是丑陋的(当然,当嵌套在“实际”模式匹配案例表达式时)。这就是我刚刚读到的关于MultiWayIf扩展的内容,它将对这种代码进行去除。 - Thomas Eding