简体   繁体   English

ghc-7.6依赖类型的类实例

[英]ghc-7.6 class instances for dependent types

Heterogeneous lists are one of the examples given for the new dependent type facility of ghc 7.6: 异构列表是为ghc 7.6的新依赖类型工具提供的示例之一:

data HList :: [*] -> * where
  HNil :: HList '[]
  HCons:: a -> HList t -> HList (a ': t)

The example list "li" compiles fine: 示例列表“li”编译正常:

li  = HCons "Int: " (HCons 234 (HCons "Integer: " (HCons 129877645 HNil)))

Obviously we would like HList to be in the Show class, but I can only come up with the following working class instantiation that uses mutually recursive constraints (superclasses): 显然我们希望HList在Show类中,但我只能提出以下使用相互递归约束(超类)的工作类实例化:

instance Show (HList '[]) where 
  show HNil = "[]"

instance (Show a, Show' (HList t)) => Show (HList (a ': t)) where
  show l  = "[" ++ show' l ++ "]"

class Show' a where
  show' :: a -> String

instance Show' (HList '[]) where
  show' HNil = ""

instance (Show a, Show' (HList t)) => Show' (HList (a ': t)) where
  show' (HCons h l) = case l of
    HNil      -> show h
    HCons _ _ -> show h ++ ", " ++ (show' l)

The code compiles fine and li is shown properly. 代码编译正常,li正确显示。 Compile flags needed are: 所需的编译标志是:

{-# LANGUAGE DataKinds, TypeOperators, KindSignatures, 
FlexibleContexts, GADTs, FlexibleInstances #-}

I tried many variants of the following far more direct definition, but it doesn't compile without me being able to understand the ghc error messages: 我尝试了以下更多直接定义的许多变体,但如果没有我能够理解ghc错误消息,它就无法编译:

instance Show (HList '[]) where 
  show HNil = "[]"

instance (Show a, Show (HList t)) => Show (HList (a ': t)) where
  show l  = "[" ++ (show' l) ++ "]" where  
    show' (HCons h s) = case s of
      HNil      -> show h
      HCons _ _ -> show h ++ ", " ++ (show' s)

Some Haskell / ghc specialist might understand why this can't work and I would be happy to hear the reason. 一些Haskell / ghc专家可能会理解为什么这不起作用,我很乐意听到原因。

Thank you 谢谢

Hans Peter 汉斯彼得


Thank you, hammar, for your two nice working examples, improving on my first example. 谢谢你,哈马尔,你的两个很好的工作例子,改进了我的第一个例子。

But I still don't understand why my second example doesn't work. 但我仍然不明白为什么我的第二个例子不起作用。 You say that "... show' only knows how to show the current element type and not the remaining ones." 你说“...... show”只知道如何显示当前的元素类型,而不是剩下的元素类型。“ But wouldn't that comment not also apply in the following (working) code: 但是这个评论不会也适用于以下(工作)代码:

instance Show (HList '[]) where show HNil = "" 

instance (Show a, Show (HList t)) => Show (HList (a ': t)) where 
   show (HCons h t) = case t of
      HNil      -> show h 
      HCons _ _ -> show h ++ ", " ++ (show t) 

As Nathan said in the comments, show' only knows how to show the current element type and not the remaining ones. 正如内森在评论中所说, show'只知道如何显示当前元素类型而不是剩余的元素类型。

As in your first example, we can get around this by making a new type class for show' , although you can get away with only one Show instance: 正如在你的第一个例子中,我们可以通过为show'创建一个新类型来解决这个问题,尽管你只能使用一个Show实例:

-- Specializing show' to HLists avoids needing a Show' (HList ts) constraint
-- here, which would require UndecidableInstances.
instance (Show' ts) => Show (HList ts) where
  show xs = "[" ++ show' xs ++ "]"

class Show' ts where
  show' :: HList ts -> String

instance Show' '[] where
  show' HNil = ""

instance (Show a, Show' ts) => Show' (a ': ts) where
  show' (HCons a s) = case s of
    HNil     -> show a
    HCons {} -> show a ++ ", " ++ show' s

Another more hackish way of getting all the necessary Show constraints into show' is to use ConstraintKinds to directly build a list of all the necessary constraints. 将所有必要的Show约束带入show'另一种更为hackish的方法是使用ConstraintKinds直接构建所有必要约束的列表。

-- In addition to the extensions in the original code:
{-# LANGUAGE TypeFamilies, ConstraintKinds, UndecidableInstances #-}
import GHC.Exts

-- ShowTypes [a, b, c, ...] = (Show a, Show b, Show c, ...)
type family ShowTypes (a :: [*]) :: Constraint
type instance ShowTypes '[] = ()
type instance ShowTypes (a ': t) = (Show a, ShowTypes t) 

instance ShowTypes ts => Show (HList ts) where
  show xs = "[" ++ show' xs ++ "]"
    where
      show' :: ShowTypes ts => HList ts -> String
      show' HNil = ""
      show' (HCons h s) = case s of
        HNil     -> show h
        HCons {} -> show h ++ ", " ++ show' s

Thanks to hammar's second solution I can now offer an even more general approach, which works for a general class (but I suppose that he had this in mind anyway): 感谢hammar的第二个解决方案,我现在可以提供一种更通用的方法,适用于一般类(但我认为无论如何他都考虑到了这一点):

type family ConstrainedTypes (a :: [*]) (f :: * -> Constraint) :: Constraint
type instance ConstrainedTypes '[] b = ()
type instance ConstrainedTypes (a ': t) b = (b a, ConstrainedTypes t b) 

instance ConstrainedTypes ts Show => Show (HList ts) where
  show xs = "[" ++ show' xs ++ "]"
    where
      show' :: ConstrainedTypes ts Show => HList ts -> String
      show' HNil = ""
      show' (HCons h s) = case s of
        HNil     -> show h
        HCons {} -> show h ++ ", " ++ show' s

Thank you again for the great help. 再次感谢您的大力帮助。

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM