如何清理模式匹配表达式(或者如何将现有类型用作受约束的类和特定类型)



考虑

data Foo1 = Foo1 { f1 :: Int }
data Foo2 = Foo2 { f2 :: Int }
data Foo3 = Foo3 { f3 :: Int }
data Thing = 
    Thing1 Foo1
  | Thing2 Foo2
  | Thnig3 Foo3
bar :: Thing -> Int
bar (Thing1 foo1) = f1 foo1
bar (Thing2 foo2) = f2 foo2
..

这显然是疯了。

我该怎么解决这个问题?

我试过

class Foo g where
  f :: g -> Int
instance Foo (Foo1) where
  f = f1
...

但这对事件没有帮助,因为如果没有所有的模式匹配,我仍然无法编写bar

我想要的是

bar :: Thing -> Int
bar (_ foo) = f foo

但这是不可能的。

(我可以根据foo的类型对Thing进行参数化,然后它就会正常工作;但我在实际代码中无法做到这一点;也就是说,我需要"Thing"是完全通用的。我很困惑,如果我已经定义了一些它们都能工作的类型类,为什么我必须为FooK进行k次模式匹配。)

如果您有一个字段,您希望通常在特定类型上使用存在主义,但偶尔会进行模式匹配,那么您可以构建一个singleton类型,将存在主义恢复为具体类型。

{-# LANGUAGE GADTs #-}
data Foo1 = Foo1 { f1 :: Int }
data Foo2 = Foo2 { f2 :: Int }
data Foo3 = Foo3 { f3 :: Int }
class Foo g where
  f :: g -> Int
-- A singleton type which introduces a unique constructor
-- for each type you want to store in the existential.
data SFoo t where
    SFoo1 :: SFoo Foo1
    SFoo2 :: SFoo Foo2
    SFoo3 :: SFoo Foo3
-- The type parameter of the singleton matches with the existential.
-- This allows us to use pattern matching to find out the real type
-- of "t" later on.
data Thing where
    Thing :: Foo t => SFoo t -> t -> Thing
-- Now you can use the existential through the type-class
bar :: Thing -> Int
bar (Thing _ foo) = f foo
-- And you can also pattern match on a specific constructor
-- when needed. Pattern matching on the singleton "SFoo1"
-- convinces the type-checker that the existential field
-- must have a type of "Foo1" which lets you use it normally.
bar2 :: Thing -> Maybe Int
bar2 (Thing SFoo1 (Foo1 i)) = Just i
bar2 _ = Nothing

存在合格类型的救援!请注意,这不是Haskell98的一部分,因此您需要启用GHC类型的系统扩展之一。

在这里,我们将Thing定义为能够容纳任何类型的对象,该对象是Foo类型类的实例。

{-# LANGUAGE ExistentialQuantification #-}
class Foo g where
  f :: g -> Int
data Foo1 = Foo1 { f1 :: Int }
instance Foo (Foo1) where f = f1
data Thing = forall a . Foo a => Thing a
bar :: Thing -> Int
bar (Thing t) = f t

请参阅此处的"异类列表"示例:https://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types

编辑1:

如果您需要能够提取特定的FooN,那么您似乎需要至少进行一次模式匹配。一种选择是进行一次模式匹配,从Thing构造通用FooThing,然后,如果可能,可以使用FooThing

{-# LANGUAGE ExistentialQuantification #-}
class Foo g where
  f :: g -> Int
data Foo1 = Foo1 { f1 :: Int }
instance Foo (Foo1) where f = f1
data Thing = Thing1 Foo1
data FooThing = forall a . Foo a => FooThing a
fooThing :: Thing -> FooThing
fooThing (Thing1 t) = FooThing t
bar :: Thing -> Int
bar = g . fooThing
  where g (FooThing t) = f t

您甚至可以更进一步,为Thing 定义Foo的实例

instance Foo (Thing) where
 f = g . fooThing
   where g (FooThing t) = f t

编辑2:

在看到shang的答案后,GADT可能是一种更好的方法,即使你只需要将Thing Foo1作为"Foo"来工作,例如

{-# LANGUAGE GADTs #-}
class Foo g where
  f :: g -> Int
data Foo1 = Foo1 { f1 :: Int }
instance Foo (Foo1) where f = f1
data Thing where
     Thing :: Foo t => t -> Thing
bar :: Thing -> Int
bar (Thing foo) = f foo

最新更新