2014-10-27 62 views
1

在Haskell語法中,我們可以有一個(抽象)類型,如[a -> b],它是函數a到b的列表。具體的類型是[Int -> Int],比如map (*) [1..10]。是否有可能有一個類似[a -> b, b -> c, c -> d, ...]類型的級聯函數列表?列表中的各個元素都是不同的(我認爲),所以我不認爲這是可能的。但是依賴類型可能嗎?它的類型簽名是什麼(最好是僞哈斯克爾語法)?級聯函數列表的類型是什麼?

+0

你不能做到這一點與在Haskell平原名單,但它是可能的。查看HList庫以獲取異構列表。要警告的是,該庫有很多擴展來獲得這種動態行爲。 – bheklilr 2014-10-27 17:27:53

+0

看看http://stackoverflow.com/questions/26565306/how-to-define-a-multiple-composition-function .... – jamshidh 2014-10-27 17:34:08

+1

這是一個(問題jamshidh鏈接的一個子集)的重複。然而,這個問題更直接地說明了這個問題。 – 2014-10-27 18:07:23

回答

6

你不能做到這一點與普通的名單,但你可以構建自己的列表類似的類型,如下所示:

{-# LANGUAGE GADTs #-} 

data CascadingList i o where 
    Id :: CascadingList i i 
    Cascade :: (b -> o) -> CascadingList i b -> CascadingList i o 

然後可以按如下方式使這些CascadingList S:

addOnePositive :: CascadingList Int Bool 
addOnePositive = Cascade (>0) $ Cascade (+1) $ Id 

你可以 '塌陷' 的名單:

collapse :: CascadingList a b -> a -> b 
collapse Id = id 
collapse (Cascade f c) = f . collapse c 

然後,你將不得不

collapse addOnePositive 0 == True 

請注意,這不考慮中間函數的類型,因此它可能不是您要查找的內容。


我剛剛意識到這與[c - > d,b - > c,a - > b]更接近。讓它更接近你的意圖是一個容易的改變;我可以編輯它,但我認爲你明白了。

+1

正如我在[回答上一個問題](http://stackoverflow.com/a/26566362/1186208)中指出的那樣,後續問題(和觀察)是:這樣的集合是什麼讓你超過函數組成? (具有不同「類別」的相同構造可能是另一回事......) – 2014-10-27 18:12:57

+0

我可以看到的一個潛在優勢是可以從這種結構中提取組合函數,但對於簡單的函數組合而言並非如此。一個人爲的例子:「(+1)。 (-1)==(-1)。 (+1)'',但'[(+1),( - 1)]/= [(-1),(+ 1)]''(顯然濫用符號)。 – 2014-10-27 19:03:34

+3

是的,我也注意到了。但你不能對他們做很多事情;除其他外,你無法從GADT之外預測它們的類型。 – 2014-10-27 19:06:40

3

上scrambledeggs'回答一個小小的改進,解決一些評論:

{-# LANGUAGE GADTs #-} 

import Data.Typeable 

data CascadingList i o where 
    Id :: CascadingList i i 
    Cascade :: Typeable b => (b -> o) -> CascadingList i b -> CascadingList i o 

現在,當你在Cascade模式匹配,你至少可以嘗試和猜測哪些類型b是利用the eqT and cast functions from Data.Typeable,如果你猜對了,你實際上可以使用裏面的函數。輕微的缺點是它只適用於具有Typeable實例(GHC至少可以導出)的類型。

5

使用DataKinds,可以公開的內部集合類型,這可能使使用組成部分容易的:

{-# LANGUAGE PolyKinds #-} 
{-# LANGUAGE TypeFamilies #-} 
{-# LANGUAGE KindSignatures #-} 
{-# LANGUAGE TypeOperators #-} 
{-# LANGUAGE DataKinds #-} 
{-# LANGUAGE GADTs #-} 
module Cascade where 
import Control.Monad ((>=>), liftM) 
import Control.Category ((>>>)) 

data Cascade (cs :: [*]) where 
    End :: Cascade '[a] 
    (:>>>) :: (a -> b) -> Cascade (b ': cs) -> Cascade (a ': b ': cs) 
infixr 5 :>>> 

-- a small example 
fs :: Cascade '[ String, Int, Float ] 
fs = read :>>> fromIntegral :>>> End 

-- alternate using functions from one chain then the other 
zigzag :: Cascade as -> Cascade as -> Cascade as 
zigzag End End = End 
zigzag (f :>>> fs) (_ :>>> gs) = f :>>> zigzag gs fs 

-- compose a chain into a single function 
compose :: Cascade (a ': as) -> a -> Last (a ': as) 
compose End = id 
compose (f :>>> fs) = f >>> compose fs 

-- generalizing Either to a union of multiple types 
data OneOf (cs :: [*]) where 
    Here :: a -> OneOf (a ': as) 
    There :: OneOf as -> OneOf (a ': as) 

-- start the cascade at any of its entry points 
fromOneOf :: Cascade cs -> OneOf cs -> Last cs 
fromOneOf fs (Here a) = compose fs a 
fromOneOf (_ :>>> fs) (There o) = fromOneOf fs o 

-- generalizing (,) to a product of multiple types 
data AllOf (cs :: [*]) where 
    None :: AllOf '[] 
    (:&) :: a -> AllOf as -> AllOf (a ': as) 
infixr 5 :& 

-- end the cascade at all of its exit points 
toAllOf :: Cascade (a ': as) -> a -> AllOf (a ': as) 
toAllOf End a  = a :& None 
toAllOf (f :>>> fs) a = a :& toAllOf fs (f a) 

-- start anywhere, and end everywhere after that 
fromOneOfToAllOf :: Cascade cs -> OneOf cs -> OneOf (Map AllOf (Tails cs)) 
fromOneOfToAllOf fs (Here a) = Here $ toAllOf fs a 
fromOneOfToAllOf (_ :>>> fs) (There o) = There $ fromOneOfToAllOf fs o 

-- type level list functions 
type family Map (f :: a -> b) (as :: [a]) where 
    Map f '[] = '[] 
    Map f (a ': as) = f a ': Map f as 

type family Last (as :: [*]) where 
    Last '[a] = a 
    Last (a ': as) = Last as 

type family Tails (as :: [a]) where 
    Tails '[] = '[ '[] ] 
    Tails (a ': as) = (a ': as) ': Tails as 

-- and you can do Monads too! 
data CascadeM (m :: * -> *) (cs :: [*]) where 
    EndM :: CascadeM m '[a] 
    (:>=>) :: (a -> m b) -> CascadeM m (b ': cs) -> CascadeM m (a ': b ': cs) 
infixr 5 :>=> 

composeM :: Monad m => CascadeM m (a ': as) -> a -> m (Last (a ': as)) 
composeM EndM = return 
composeM (f :>=> fs) = f >=> composeM fs 

fromOneOfM :: Monad m => CascadeM m cs -> OneOf cs -> m (Last cs) 
fromOneOfM fs (Here a) = composeM fs a 
fromOneOfM (_ :>=> fs) (There o) = fromOneOfM fs o 

-- end the cascade at all of its exit points 
toAllOfM :: Monad m => CascadeM m (a ': as) -> a -> m (AllOf (a ': as)) 
toAllOfM EndM a  = return $ a :& None 
toAllOfM (f :>=> fs) a = do 
    as <- toAllOfM fs =<< f a 
    return $ a :& as 

-- start anywhere, and end everywhere after that 
fromOneOfToAllOfM :: Monad m => CascadeM m cs -> OneOf cs -> m (OneOf (Map AllOf (Tails cs))) 
fromOneOfToAllOfM fs (Here a) = Here `liftM` toAllOfM fs a 
fromOneOfToAllOfM (_ :>=> fs) (There o) = There `liftM` fromOneOfToAllOfM fs o 
+0

我認爲'Chain'也可以被實現爲(封閉)類型的類型,因爲類型參數'cs'明確指出將使用哪些構造函數。 – 2014-10-27 20:55:28

+0

Christian Conkle:是的,我做了這個[OneOf'](http://stackoverflow.com/questions/25414521/types-for-parser-combinators)。我現在在瞎搞。 – rampion 2014-10-27 20:59:15

+0

Christian Conkle:現在我放棄了封閉型家庭,因爲當我試圖做任何有趣的事情時,我總是感到內射型錯誤。 – rampion 2014-10-28 01:19:39