2013-07-06 70 views
10

我最近了解了一些關於F-代數的知識: https://www.fpcomplete.com/user/bartosz/understanding-algebras。 我想將這個功能提升到更高級的類型(索引和更高主動)。 此外,我檢查了「給予Haskell促銷」(http://research.microsoft.com/en-us/people/dimitris/fc-kind-poly.pdf),這是非常有用的,因爲它給我自己模糊的「發明」的名稱。如何使變形與參數化/索引類型一起工作?

但是,我似乎無法創建適用於所有形狀的統一方法。代數需要一些「載體類型」,但我們所穿過的結構需要一定的形狀(本身,遞歸地應用),所以我想出了一個可以攜帶任何類型的「虛擬」容器,但是它的形狀是預期。然後我使用一個類型家庭來耦合這些。

這種方法似乎工作,導致我的'cata'功能相當通用的簽名。然而,我使用的其他東西(Mu,代數)仍然需要爲每個形狀分別版本,只是爲了傳遞一堆類型變量。我希望像PolyKinds這樣的東西能夠幫助我(我成功地用它來塑造虛擬類型),但它似乎只是用來反其道而行之。

由於IFunctor1和IFunctor2沒有額外的變量,我試圖通過附加(通過類型族)索引保留函數類型來統一它們,但由於存在量化,這似乎是不允許的,所以我離開了也有多個版本。

有什麼辦法統一這兩種情況?我忽略了一些技巧,還是現在這只是一個限制? 還有其他的事情可以簡化嗎?

{-# LANGUAGE DataKinds     #-} 
{-# LANGUAGE ExistentialQuantification #-} 
{-# LANGUAGE GADTs      #-} 
{-# LANGUAGE PolyKinds     #-} 
{-# LANGUAGE Rank2Types    #-} 
{-# LANGUAGE StandaloneDeriving  #-} 
{-# LANGUAGE TypeFamilies    #-} 
{-# LANGUAGE TypeOperators    #-} 
{-# LANGUAGE UndecidableInstances  #-} 
module Cata where 

-- 'Fix' for indexed types (1 index) 
newtype Mu1 f a = Roll1 { unRoll1 :: f (Mu1 f) a } 
deriving instance Show (f (Mu1 f) a) => Show (Mu1 f a) 

-- 'Fix' for indexed types (2 index) 
newtype Mu2 f a b = Roll2 { unRoll2 :: f (Mu2 f) a b } 
deriving instance Show (f (Mu2 f) a b) => Show (Mu2 f a b) 

-- index-preserving function (1 index) 
type s :-> t = forall i. s i -> t i 

-- index-preserving function (2 index) 
type s :--> t = forall i j. s i j -> t i j 

-- indexed functor (1 index) 
class IFunctor1 f where 
    imap1 :: (s :-> t) -> (f s :-> f t) 

-- indexed functor (2 index) 
class IFunctor2 f where 
    imap2 :: (s :--> t) -> (f s :--> f t) 

-- dummy container type to store a solid result type 
-- the shape should follow an indexed type 
type family Dummy (x :: i -> k) :: * -> k 

type Algebra1 f a = forall t. f ((Dummy f) a) t -> (Dummy f) a t 
type Algebra2 f a = forall s t. f ((Dummy f) a) s t -> (Dummy f) a s t 

cata1 :: IFunctor1 f => Algebra1 f a -> Mu1 f t -> (Dummy f) a t 
cata1 alg = alg . imap1 (cata1 alg) . unRoll1 

cata2 :: IFunctor2 f => Algebra2 f a -> Mu2 f s t -> (Dummy f) a s t 
cata2 alg = alg . imap2 (cata2 alg) . unRoll2 

和2層示例結構的工作與:

ExprF1似乎是一個正常的有用的東西,在安裝嵌入型到對象語言。

ExprF2是人爲設計的(額外的參數恰好被解除(DataKinds)),只是爲了找出「generic」cata2是否能夠處理這些形狀。

-- our indexed type, which we want to use in an F-algebra (1 index) 
data ExprF1 f t where 
    ConstI1 :: Int -> ExprF1 f Int 
    ConstB1 :: Bool -> ExprF1 f Bool 
    Add1 :: f Int -> f Int -> ExprF1 f Int 
    Mul1 :: f Int -> f Int -> ExprF1 f Int 
    If1  :: f Bool -> f t -> f t -> ExprF1 f t 
deriving instance (Show (f t), Show (f Bool)) => Show (ExprF1 f t) 

-- our indexed type, which we want to use in an F-algebra (2 index) 
data ExprF2 f s t where 
    ConstI2 :: Int -> ExprF2 f Int True 
    ConstB2 :: Bool -> ExprF2 f Bool True 
    Add2 :: f Int True -> f Int True -> ExprF2 f Int True 
    Mul2 :: f Int True -> f Int True -> ExprF2 f Int True 
    If2  :: f Bool True -> f t True -> f t True -> ExprF2 f t True 
deriving instance (Show (f s t), Show (f Bool t)) => Show (ExprF2 f s t) 

-- mapper for f-algebra (1 index) 
instance IFunctor1 ExprF1 where 
    imap1 _ (ConstI1 x) = ConstI1 x 
    imap1 _ (ConstB1 x) = ConstB1 x 
    imap1 eval (x `Add1` y) = eval x `Add1` eval y 
    imap1 eval (x `Mul1` y) = eval x `Mul1` eval y 
    imap1 eval (If1 p t e) = If1 (eval p) (eval t) (eval e) 

-- mapper for f-algebra (2 index) 
instance IFunctor2 ExprF2 where 
    imap2 _ (ConstI2 x) = ConstI2 x 
    imap2 _ (ConstB2 x) = ConstB2 x 
    imap2 eval (x `Add2` y) = eval x `Add2` eval y 
    imap2 eval (x `Mul2` y) = eval x `Mul2` eval y 
    imap2 eval (If2 p t e) = If2 (eval p) (eval t) (eval e) 

-- turned into a nested expression 
type Expr1 = Mu1 ExprF1 

-- turned into a nested expression 
type Expr2 = Mu2 ExprF2 

-- dummy containers 
newtype X1 x y = X1 x deriving Show 
newtype X2 x y z = X2 x deriving Show 

type instance Dummy ExprF1 = X1 
type instance Dummy ExprF2 = X2 


-- a simple example agebra that evaluates the expression 
-- turning bools into 0/1  
alg1 :: Algebra1 ExprF1 Int 
alg1 (ConstI1 x)   = X1 x 
alg1 (ConstB1 False)  = X1 0 
alg1 (ConstB1 True)   = X1 1 
alg1 ((X1 x) `Add1` (X1 y)) = X1 $ x + y 
alg1 ((X1 x) `Mul1` (X1 y)) = X1 $ x * y 
alg1 (If1 (X1 0) _ (X1 e)) = X1 e 
alg1 (If1 _ (X1 t) _)  = X1 t 

alg2 :: Algebra2 ExprF2 Int 
alg2 (ConstI2 x)   = X2 x 
alg2 (ConstB2 False)  = X2 0 
alg2 (ConstB2 True)   = X2 1 
alg2 ((X2 x) `Add2` (X2 y)) = X2 $ x + y 
alg2 ((X2 x) `Mul2` (X2 y)) = X2 $ x * y 
alg2 (If2 (X2 0) _ (X2 e)) = X2 e 
alg2 (If2 _ (X2 t) _)  = X2 t 


-- simple helpers for construction 
ci1 :: Int -> Expr1 Int 
ci1 = Roll1 . ConstI1 

cb1 :: Bool -> Expr1 Bool 
cb1 = Roll1 . ConstB1 

if1 :: Expr1 Bool -> Expr1 a -> Expr1 a -> Expr1 a 
if1 p t e = Roll1 $ If1 p t e 

add1 :: Expr1 Int -> Expr1 Int -> Expr1 Int 
add1 x y = Roll1 $ Add1 x y 

mul1 :: Expr1 Int -> Expr1 Int -> Expr1 Int 
mul1 x y = Roll1 $ Mul1 x y 

ci2 :: Int -> Expr2 Int True 
ci2 = Roll2 . ConstI2 

cb2 :: Bool -> Expr2 Bool True 
cb2 = Roll2 . ConstB2 

if2 :: Expr2 Bool True -> Expr2 a True-> Expr2 a True -> Expr2 a True 
if2 p t e = Roll2 $ If2 p t e 

add2 :: Expr2 Int True -> Expr2 Int True -> Expr2 Int True 
add2 x y = Roll2 $ Add2 x y 

mul2 :: Expr2 Int True -> Expr2 Int True -> Expr2 Int True 
mul2 x y = Roll2 $ Mul2 x y 


-- test case 
test1 :: Expr1 Int 
test1 = if1 (cb1 True) 
      (ci1 3 `mul1` ci1 4 `add1` ci1 5) 
      (ci1 2) 

test2 :: Expr2 Int True 
test2 = if2 (cb2 True) 
      (ci2 3 `mul2` ci2 4 `add2` ci2 5) 
      (ci2 2) 


main :: IO() 
main = let (X1 x1) = cata1 alg1 test1 
      (X2 x2) = cata2 alg2 test2 
     in do print x1 
      print x2 

輸出:

17 
17 
+4

對索引而不是使用兩個索引更統一。我的建議是,在處理索引集時,只要可能就使用一個索引,並利用您的自由來構建具有提升類型的索引。 1,2,4,8,指數的時間! – pigworker

+1

@pigworker:是的,這確實是一個很好的解決方法。 然後我只需要cata1和朋友。 –

+0

__Good__問題,挑起偉大的一個偉大的答案。不可能有很多標籤,你可以從基礎到崇高。耶Haskell。 – AndrewC

回答

12

我寫了一篇關於這個話題在2009年它被稱爲"Slicing It"談話肯定地指出了我的Strathclyde同事Johann和Ghani關於GADT的初始代數語義學的工作。我使用了SHE提供的用於編寫數據索引類型的符號,但它已被「促銷」故事所取代。

根據我的評論,談話的關鍵是系統地使用恰好一個索引,而不是利用其種類可能變化的事實。

所以事實上,我們已經(使用我當前的首選 「戈西尼(Goscinny)和Uderzo」 的名字)

type s :-> t = forall i. s i -> t i 

class FunctorIx f where 
    mapIx :: (s :-> t) -> (f s :-> f t) 

現在,您可以顯示FunctorIx下固定點關閉。關鍵是將兩個索引集合組合成一個提供索引選擇的集合。

data Case (f :: i -> *) (g :: j -> *) (b :: Either i j) :: * where 
    L :: f i -> Case f g (Left i) 
    R :: g j -> Case f g (Right j) 

(<?>) :: (f :-> f') -> (g :-> g') -> Case f g :-> Case f' g' 
(f <?> g) (L x) = L (f x) 
(f <?> g) (R x) = R (g x) 

現在,我們現在可以採取函子,其「包含的元素」代表不是「有效載荷」或「遞歸子」的固定點。

data MuIx (f :: (Either i j -> *) -> j -> *) :: (i -> *) -> j -> * where 
    InIx :: f (Case x (MuIx f x)) j -> MuIx f x j 

其結果是,我們可以在mapIx 「有效載荷」 ......

instance FunctorIx f => FunctorIx (MuIx f) where 
    mapIx f (InIx xs) = InIx (mapIx (f <?> mapIx f) xs) 

...或寫在 「遞歸子」 一catamorphism ...

foldIx :: FunctorIx f => (f (Case x t) :-> t) -> MuIx f x :-> t 
foldIx f (InIx xs) = f (mapIx (id <?> foldIx f) xs) 

......或者兩者兼而有之。

mapFoldIx :: FunctorIx f => (x :-> y) -> (f (Case y t) :-> t) -> MuIx f x :-> t 
mapFoldIx e f (InIx xs) = f (mapIx (e <?> mapFoldIx e f) xs) 

FunctorIx喜的是它有如此出色的封閉性,這要歸功於改變索引種的能力。 MuIx允許有效載荷的概念,並可迭代。因此,我們有動力使用結構化指數而不是多指數。

+1

哇。這讓我的思緒稍稍鬆了一點!我可以稍微看看它是如何工作的,但我只能夢想自己製作類似的東西。它在很多情況下非常有用,包括我的問題,所以我會將答案轉換爲這個。你能否詳細說明你的意思是「閉合」和「閉合屬性」?我沒有一個廣泛的數學背景:( 作爲一個旁註,FunctorIx,FoldIx和朋友提醒我一個caroon:P –

+2

未索引的故事定義'Mu(f :: * - > *):: * ',其中一些'Functor f'描述了遞歸數據類型的節點結構:'f'抽象遞歸子結構的位置,但是'Mu f'本身不是'Functor',即使它有一個「元素」的概念。考慮列表:列表節點可以有一個列表元素和一個子列表的位置,你可以通過獲取描述一個節點的bifunctor(即不是「Functor」)的固定點來描述'Functor'列表但遞歸索引仿函數是其他索引仿函數的固定點,所以索引函數在一個固定點下關閉。 – pigworker

3

如果我正確地理解它,這恰恰是由約翰和加尼的解決了這個問題「初始代數語義是夠了!」

https://personal.cis.strath.ac.uk/neil.ghani/papers/ghani-tlca07.pdf

具體見他們hfold

編輯:對於GADT情況下,看到自己以後的論文 「基金會使用GADTs結構化編程」。需要注意的是,他們遇到可使用PolyKinds,這是我們現在需要解決的一個障礙:http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.111.2948

本博客文章也可能感興趣:http://www.timphilipwilliams.com/posts/2013-01-16-fixing-gadts.html

+0

看起來確實是一篇非常有趣的論文。 但是,我不確定它處理我的問題,雖然(索引類型通過GADT)。 本文的最後一段明確指出GADTs可能是未來的工作: 「最後,本文的技術可以提供對高級數據類型的摺疊,構建和融合規則的理解,如混合方差數據類型, GADT和依賴類型。「 –

+0

酷,很多閱讀:) 我可能需要一些時間來了解是否有一個完美的解決方案,但我相信它會給我很多正確的方向步驟,所以我會接受你的答案。謝謝! –

相關問題