哈斯克尔中 OOP 风格的可展示对象列表



我想建立一个不同事物的列表,这些事物有一个共同的属性,即它们可以变成字符串。面向对象的方法很简单:定义接口Showable并使感兴趣的类实现它。当你不能改变类时,第二点原则上可能是一个问题,但让我们假装情况并非如此。然后,您创建一个Showable列表,并用这些类的对象填充它,而没有任何额外的噪音(例如,上投通常是隐式完成的(。这里给出了Java中的概念证明。

我的问题是我在哈斯克尔有什么选择?下面我将讨论我尝试过的方法,这些方法并不能真正满足我。

方法1:存在主义。有效但丑陋。

{-# LANGUAGE ExistentialQuantification #-}
data Showable = forall a. Show a => Sh a
aList :: [Showable]
aList = [Sh (1 :: Int), Sh "abc"]

我在这里的主要缺点是在填写列表时需要Sh。这与在 OO 语言中隐式完成的向上转换操作非常相似。

更一般地说,虚拟包装器Showable语言中已有的东西 - Show类型类 - 在我的代码中添加了额外的噪音。白搭。

方法2:谓词。需要但不起作用。

对我来说,这样的列表最直接的类型以及我真正想要的是:

{-# LANGUAGE ImpredicativeTypes #-}
aList :: [forall a. Show a => a]
aList = [(1 :: Int), "abc"]

除此之外(正如我所听说的(,ImpredicativeTypes"充其量是脆弱的,最坏的情况是破碎的"它不编译:

Couldn't match expected type ‘a’ with actual type ‘Int’
  ‘a’ is a rigid type variable bound by
      a type expected by the context: Show a => a

和同样的错误对于"abc".(注意 1 的类型签名:没有它,我会收到更奇怪的消息:Could not deduce (Num a) arising from the literal ‘1’ (。

方法3:排名N类型以及某种功能列表(差异列表?

与其有问题的ImpredicativeTypes人们可能更喜欢更稳定和广泛接受的RankNTypes。这基本上意味着:移动所需的forall a. Show a => a类型构造函数(即 [] ( 到普通函数类型。因此,我们需要将列表表示为普通函数。我几乎听说有这样的表示。我听说过的是差异列表。但是在Dlist包中,主要类型是很好的旧data所以我们回到谓词。我没有进一步调查这一行,因为我怀疑它可能产生比方法 1 更详细的代码。但如果你认为不会,请给我举个例子。

一句话:你会如何在哈斯克尔中完成这样的任务?您能否提供比 OO 语言更简洁的解决方案(尤其是代替填写列表 — 请参阅方法 1 中的代码注释(?您能否评论一下上面列出的方法的相关性?

UPD(基于第一条评论(:为了可读性,这个问题当然是简化的。真正的问题更多的是如何存储共享相同类型类的东西,即以后可以通过多种方式进行处理(Show只有一个方法,但其他类可以有多个(。这排除了建议在填写列表时正确应用show方法的解决方案。

由于 Haskell 中的求值是懒惰的,那么只创建一个实际字符串的列表怎么样?

showables = [ show 1, show "blah", show 3.14 ]

HList式解决方案将起作用,但是如果您只需要使用受约束的存在列表并且不需要其他HList机制,则可以降低复杂性。

以下是我在existentialist包中如何处理此问题:

{-# LANGUAGE ConstraintKinds, ExistentialQuantification, RankNTypes #-}
data ConstrList c = forall a. c a => a :> ConstrList c
                  | Nil
infixr :>
constrMap :: (forall a. c a => a -> b) -> ConstrList c -> [b]
constrMap f (x :> xs) = f x : constrMap f xs
constrMap f Nil       = []

然后可以像这样使用:

example :: [String]
example
  = constrMap show
              (( 'a'
              :> True
              :> ()
              :> Nil) :: ConstrList Show)

如果你有一个很大的列表,或者如果你必须对一个受约束的存在列表进行大量操作,这可能会很有用。

使用此方法,也不需要在类型(或元素的原始类型(中对列表的长度进行编码。根据情况,这可能是一件好事或一件坏事。如果要保留所有原始类型信息,则HList可能是要走的路。

此外,如果(就像Show的情况一样(只有一个类方法,我推荐的方法是直接将该方法应用于列表中的每个项目,如 ErikR 的答案或 phadej 答案中的第一种技术。

听起来实际问题比Show值列表更复杂,因此如果没有更具体的信息,很难明确建议其中哪一个最合适。

不过,其中一种方法可能会很好地工作(除非可以简化代码本身的体系结构,以便它首先不会遇到问题(。

推广到包含在高级类型中的存在主义

这可以推广到更高的种类,如下所示:

data AnyList c f = forall a. c a => f a :| (AnyList c f)
                 | Nil
infixr :|
anyMap :: (forall a. c a => f a -> b) -> AnyList c f -> [b]
anyMap g (x :| xs) = g x : anyMap g xs
anyMap g Nil       = []

使用它,我们可以(例如(创建一个具有Show -able 结果类型的函数列表。

example2 :: Int -> [String]
example2 x = anyMap (m -> show (m x))
                    (( f
                    :| g
                    :| h
                    :| Nil) :: AnyList Show ((->) Int))
  where
    f :: Int -> String
    f = show
    g :: Int -> Bool
    g = (< 3)
    h :: Int -> ()
    h _ = ()

我们可以通过定义以下方法看到这是一个真正的概括:

type ConstrList c = AnyList c Identity
(>:) :: forall c a. c a => a -> AnyList c Identity -> AnyList c Identity
x >: xs  = Identity x :| xs
infixr >:
constrMap :: (forall a. c a => a -> b) -> AnyList c Identity -> [b]
constrMap f (Identity x :| xs) = f x : constrMap f xs
constrMap f Nil                = []

这允许本文第一部分中的原始example使用这种新的、更通用的公式工作,除了将:>更改为>:之外,无需更改现有example代码(即使是这种小的更改也可以通过模式同义词来避免。我不完全确定,因为我没有尝试过,有时模式同义词以我不完全理解的方式与存在量化相互作用(。

如果你真的,真的想要,你可以使用异构列表。这种方法对 Show 确实没有用,因为它只有一个方法,你所能做的就是应用它,但是如果你的类有多个方法,这可能很有用。

{-# LANGUAGE PolyKinds, KindSignatures, GADTs, TypeFamilies
   , TypeOperators, DataKinds, ConstraintKinds, RankNTypes, PatternSynonyms  #-} 
import Data.List (intercalate)
import GHC.Prim (Constraint)
infixr 5 :&
data HList xs where 
  None :: HList '[] 
  (:&) :: a -> HList bs -> HList (a ': bs) 
-- | Constraint All c xs holds if c holds for all x in xs
type family All (c :: k -> Constraint) xs :: Constraint where 
  All c '[] = () 
  All c (x ': xs) = (c x, All c xs) 
-- | The list whose element types are unknown, but known to satisfy
--   a class predicate. 
data CList c where CL :: All c xs => HList xs -> CList c  
cons :: c a => a -> CList c -> CList c
cons a (CL xs) = CL (a :& xs) 
empty :: CList c 
empty = CL None 
uncons :: (forall a . c a => a -> CList c -> r) -> r -> CList c -> r 
uncons _ n (CL None) = n 
uncons c n (CL (x :& xs)) = c x (CL xs) 
foldrC :: (forall a . c a => a -> r -> r) -> r -> CList c -> r 
foldrC f z = go where go = uncons (x -> f x . go) z 
showAll :: CList Show -> String 
showAll l = "[" ++ intercalate "," (foldrC (x xs -> show x : xs) [] l) ++ "]" 
test = putStrLn $ showAll $ CL $ 
  1 :& 
  'a' :& 
  "foo" :& 
  [2.3, 2.5 .. 3] :& 
  None 

您可以创建自己的运算符来减少语法噪音:

infixr 5 <:
(<:) :: Show a => a -> [String] -> [String]
x <: l = show x : l

所以你可以做到:

λ > (1 :: Int) <: True <: "abs" <: []
["1","True",""abs""]

这不是[1 :: Int, True, "abs"],但不会太长。

不幸的是,您无法将[...]语法与 RebindableSyntax 重新绑定。


另一种方法是使用 HList 并保留所有类型的信息,即没有向下转换,没有向上转换:

{-# LANGUAGE ConstraintKinds       #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE PolyKinds             #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE TypeOperators         #-}
{-# LANGUAGE UndecidableInstances  #-}
import GHC.Exts (Constraint)
infixr 5 :::
type family All (c :: k -> Constraint) (xs :: [k]) :: Constraint where
  All c '[]       = ()
  All c (x ': xs) = (c x, All c xs)
data HList as where
  HNil :: HList '[]
  (:::) :: a -> HList as -> HList (a ': as)
instance All Show as => Show (HList as) where
  showsPrec d HNil       = showString "HNil"
  showsPrec d (x ::: xs) = showParen (d > 5) (showsPrec 5 x)
                         . showString " ::: "
                         . showParen (d > 5) (showsPrec 5 xs)

毕竟:

λ *Main > (1 :: Int) ::: True ::: "foo" ::: HNil
1 ::: True ::: "foo" ::: HNil
λ *Main > :t (1 :: Int) ::: True ::: "foo" ::: HNil
(1 :: Int) ::: True ::: "foo" ::: HNil
  :: HList '[Int, Bool, [Char]]
有多种

方法可以编码异构列表HList是一种,也有generics-sopNP I xs。这取决于你在更大的上下文中试图实现什么,如果这是你需要的,那么这种保留所有类型的方法就是你需要的。

我会做这样的事情:

newtype Strings = Strings { getStrings :: [String] }
newtype DiffList a = DiffList { getDiffList :: [a] -> [a] }
instance Monoid (DiffList a) where
    mempty                          = DiffList id
    DiffList f `mappend` DiffList g = DiffList (f . g)
class ShowList a where
    showList' :: DiffList String -> a
instance ShowList Strings where
    showList' (DiffList xs) = Strings (xs [])
instance (Show a, ShowList b) => ShowList (a -> b) where
    showList' xs x = showList' $ xs `mappend` DiffList (show x :)
showList = showList' mempty

现在,您可以按如下方式创建ShowList

myShowList = showList 1 "blah" 3.14

您可以使用getStrings获取字符串列表,如下所示:

myStrings = getStrings myShowList
以下是

正在发生的事情:

  1. ShowList a => a类型的值可以是:

      包装
    1. Strings newtype 包装器中的字符串列表。
    2. 或者从Show实例到ShowList实例的函数。
  2. 这意味着函数 showList 是一个可变参数函数,它接受任意数量的可打印值,并最终返回包装在 Strings newtype 包装器中的字符串列表。

  3. 最终可以对 ShowList a => a 类型的值调用 getStrings 以获取最终结果。此外,您不需要自己执行任何显式类型强制

优势:

  1. 您可以随时将新元素添加到列表中。
  2. 语法简洁。您不必在每个元素的前面手动添加show
  3. 它不使用任何语言扩展。因此,它也适用于 Haskell 98。
  4. 您可以两全其美,类型安全和出色的语法。
  5. 使用差异列表,您可以在线性时间内构建结果。

有关具有可变参数的函数的更多信息,请阅读以下问题的答案:

Haskell打印f如何工作?

我的回答与 ErikR 的答案基本相同:最能体现您需求的类型是 [String] 。 但我会更深入地探讨我认为证明这个答案合理的逻辑。 关键在于问题的这句话:

[...]具有一个共同属性的事物,即它们可以变成字符串。

我们称这种类型为Stringable。 但现在关键的观察结果是:

  • StringableString

也就是说,如果你上面的语句是Stringable类型的整个规范,那么有一对函数具有这些签名:

toString :: Stringable -> String
toStringable :: String -> Stringable

。使得这两个函数是相反的。 当两种类型同构时,任何使用其中一种类型的程序都可以根据另一种类型重写,而无需对其语义进行任何更改。 所以Stringable不让你做任何String不让你做的事情!

更具体地说,关键是无论如何,这种重构都可以保证工作:

  1. 在程序中的每一点,您将对象变成Stringable并将其粘贴到[Stringable]中,将对象变成String并将其粘贴到[String]中。
  2. 在程序中通过应用toString来使用Stringable的每个点,您现在可以消除对toString的调用。

注意这个参数推广到比Stringable更复杂的类型,有许多"方法"。 因此,例如,"可以变成StringInt的东西"的类型与(String, Int)同构。 "你可以变成String或将它们与Foo组合以产生Bar的东西"的类型与(String, Foo -> Bar)同构。 等等。 基本上,这种逻辑导致了其他答案提出的"方法记录"编码。

我认为从中吸取的教训如下:你需要一个比"可以变成字符串"更丰富的规范,以便证明使用你提出的任何机制是合理的。 因此,例如,如果我们添加Stringable值可以向下转换为原始类型的要求,那么存在类型现在可能变得合理:

{-# LANGUAGE GADTs #-}
import Data.Typeable
data Showable = Showable
    Showable :: (Show a, Typeable a) => a -> Stringable
downcast :: Typeable a => Showable -> Maybe a
downcast (Showable a) = cast a

这种Showable类型与 String 不同构,因为Typeable约束允许我们实现 downcast 函数,该函数允许我们区分产生相同字符串的不同Showable。 这个想法的更丰富版本可以在这个"形状示例"Gist中看到。

您可以在列表中存储部分应用的函数。

假设我们正在构建一个具有不同形状的光线追踪器,您可以相交。

data Sphere = ...
data Triangle = ...
data Ray = ...
data IntersectionResult = ...
class Intersect t where
      intersect :: t -> Ray -> Maybe IntersectionResult
instance Intersect Sphere where ...
instance Intersect Triangle where ...

现在,我们可以部分应用 intersect 来获取Ray -> Maybe IntersectionResult列表,例如:

myList :: [(Ray -> Maybe IntersectionResult)]
myList = [intersect sphere, intersect triangle, ...]

现在,如果你想得到所有的交叉点,你可以写:

map ($ ray) myList -- or map (f -> f ray) myList

这可以扩展一点以处理具有多个函数的接口,例如,如果您希望能够获得形状:

class ShapeWithSomething t where
        getSomething :: t -> OtherParam -> Float
data ShapeIntersectAndSomething = ShapeIntersectAndSomething {
          intersect :: Ray -> Maybe IntersectionResult,
          getSomething :: OtherParam -> Float}

我不知道的是这种方法的开销。我们需要存储指向函数的指针和指向形状的指针,这对于接口的每个函数来说都是如此,这与 OO 语言中通常使用的共享 vtable 相比要多得多。我不知道GHC是否能够优化这一点。

问题的核心是:你想在运行时调度(阅读选择要调用的函数(,这取决于对象的"类型"是什么。在Haskell中,这可以通过将数据包装成sum数据类型来实现(这里称为ShowableInterface(:

data ShowableInterface = ShowInt Int | ShowApple Apple | ShowBusiness Business
instance Show ShowableInterface where
   show (ShowInt i)      = show i
   show (ShowApple a)    = show a
   show (ShowBusiness b) = show b  
list=[ShowInt 2, ShowApple CrunchyGold, ShowBusiness MoulinRouge]
show list

将对应于Java中的类似内容:

class Int implements ShowableInterface
{
   public show {return Integer.asString(i)};
}
class Apple implements ShowableInterface
{
   public show {return this.name};
}
class ShowBusiness implements ShowableInterface
{
   public show {return this.fancyName};
}
List list = new ArrayList (new Apple("CrunchyGold"), 
                           new ShowBusiness("MoulingRouge"), new Integer(2));

所以在Haskell中你需要显式地将东西包装到ShowableInterface中,在Java中,这种包装是在对象创建时隐式完成的。

感谢 #haskell IRC在一年前向我解释了这一点,大约一年前。

最新更新