2017-06-21 61 views
1

我大概想是這樣的:擴展記錄(我認爲)

data A = ... 
data B = ... 
data C = ... 

class HasA t where 
    getA :: t -> A 

class HasB t where 
    getB :: t -> B 

class HasC t where 
    getC :: t -> C 

所以我可以做這樣的事情(僞代碼如下):

a :: A 
b :: B 

x = mkRecord { elemA a, elemB b } 
y = mkRecord { elemB b, elemA a } 

-- type of `x` == type of `y` 

當然,只有適當的get職能的工作,在上述情況下爲getAgetB

我也會喜歡下列功能

slice :: Subset a b => a -> b 
slice x = -- just remove the bits of x that aren't in type b. 

add :: e -> a -> a ++ e 
add e x = -- add an element to the "record" (compile error if it's already there) 

我覺得這不是一個新問題,所以也許是這個分辨率已經存在。請注意,我不需要解決方案是可擴展的,我需要處理的類型數量是有限且已知的,但當然可擴展的並不會造成傷害。

我發現了幾個包,似乎在我正在尋找的領域,即HListextensible(也許可擴展性更好,因爲我希望我的記錄無序)。我在Hackage文檔中有點迷茫,所以我只想要一些示例代碼(或者一些示例代碼的鏈接),它們大致可以實現我正在尋找的內容。

回答

1

這正是HList的好處。但是,由於我目前沒有正確的設置來測試HList程序包(此外,它還有more confusing data definitions),下面是HList的一個簡單示例,它使用singletons作爲類型級別的列表。

{-# LANGUAGE DataKinds, TypeOperators, GADTs,TypeFamilies, UndecidableInstances, 
    PolyKinds, FlexibleInstances, MultiParamTypeClasses 
    #-} 

import Data.Singletons 
import Data.Promotion.Prelude.List 

data HList (l :: [*]) where 
    HNil :: HList '[] 
    HCons :: x -> HList xs -> HList (x ': xs) 

add功能是最簡單的:它只是HCons

add :: x -> HList xs -> HList (x ': xs) 
add = HCons 

東西更有意思的是,結合兩個記錄:現在

-- Notice we are using `:++` from singletons 
combine :: HList xs -> HList ys -> HList (xs :++ ys) 
combine HNil xs = xs 
combine (x `HCons` xs) ys = x `HCons` (xs `combine` ys) 

,爲您get功能,您需要根據類型級別列表進行分派。要做到這一點,你需要一個重疊類型的類。

class Has x xs where 
    get :: xs -> x 

instance {-# OVERLAPS #-} Has x (HList (x ': xs)) where 
    get (x `HCons` _) = x 

instance Has x (HList xs) => Has x (HList (y ': xs)) where 
    get (_ `HCons` xs) = get xs 

最後,我們可以使用Has定義一個類似Subset類。和以前一樣。

class Subset ys xs where 
    slice :: xs -> ys 

instance Subset (HList '[]) (HList xs) where 
    slice _ = HNil 

instance (Get y (HList xs), Subset (HList ys) (HList xs)) => 
      Subset (HList (y ': ys)) (HList xs) where 
    slice xs = get xs `HCons` slice xs 

正如你在括號提及,簡單HList形式並不能保證你只有一個任何類型的字段(所以get剛剛返回的第一個字段,忽略其它)。如果你想要唯一性,你可以添加一個約束到構造函數HList

data Record (l :: [*]) where 
    Nil :: Record '[] 
    Cons :: (NotElem x xs ~ 'True) => x -> Record xs -> Record (x ': xs) 

但是,使用Record看起來像它涉及到一些證據定義Subset。 :)