2014-11-22 53 views
1

我需要爲我正在處理的東西實現一個通用堆棧。這個堆棧應該能夠保存不同類型的元素。例如(1,'c',True,「字符串」)。要支持的功能是top,pop和push。Haskell中的一般'無類型'堆棧

元組是最自然的想法。

push x s = (x,s) 
pop s = snd s 
top s = (fst s, s) 

但我也需要支持空棧。這裏,pop和top沒有在()上定義。 所以我嘗試創建一個新類型。

data Stack = Empty | forall x. Cons (x, Stack) 
push x s = Cons (x,s) 
pop s = case s of 
     Empty -> Left s 
     Cons (x, y) -> Right y 
top s = case s of 
     Empty -> (Left(), s) 
     Cons (x,y) -> (Right x, s) 

這裏,頂給我一個錯誤:

Couldn't match expected type ‘b’ with actual type ‘x’ 
    because type variable ‘x’ would escape its scope 
This (rigid, skolem) type variable is bound by 
    a pattern with constructor 
    Cons :: forall x. (x, Stack) -> Stack, 
    in a case alternative 
    at try.hs:11:9-18 
Relevant bindings include 
    x :: x (bound at try.hs:11:15) 
    top :: Stack -> (Either() b, Stack) (bound at try.hs:9:1) 
In the first argument of ‘Right’, namely ‘x’ 
In the expression: Right x 

如果我解決這個具有:

data Stack x = Empty | forall y. Cons (x, Stack y) 

我得到同樣的錯誤彈出。

我也嘗試添加此:

type AnyStack = forall x. Stack x 

但同樣得到類似的錯誤:

Couldn't match expected type ‘b’ with actual type ‘Stack y’ 
    because type variable ‘y’ would escape its scope 
This (rigid, skolem) type variable is bound by 
    a pattern with constructor 
    Cons :: forall x y. (x, Stack y) -> Stack x, 
    in a case alternative 
    at try.hs:8:9-19 
Relevant bindings include 
    y :: Stack y (bound at try.hs:8:18) 
    pop :: Stack t -> Either (Stack t) b (bound at try.hs:6:1) 
In the first argument of ‘Right’, namely ‘y’ 
In the expression: Right y 

誰能幫我出正確的類型簽名或類型定義爲這種堆疊?或者,也許可以指點一下與此有關的一些很好的參考?

非常感謝先進!

編輯:

這將會是完美的,如果我還能夠包括對於這種疊層get函數。給定一個整數i和一個堆棧s,get會返回s的第i個元素。我希望我能夠在推動,彈出和頂部排序後自己做到這一點,但我仍然無法做到。關於這個傢伙的任何想法?

回答

1

您是否需要將其歸類?如果你願意使用高級GHC功能,你可以做這樣的事情:

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

module Stack (Stack(..), push, pop, top, empty) where 

data Stack (h :: [*]) where 
    Empty :: Stack '[] 
    Push :: x -> Stack xs -> Stack (x ': xs) 

instance Show (Stack '[]) where 
    showsPrec d Empty = showParen (d > 11) $ showString "Empty" 

instance (Show x, Show (Stack xs)) => Show (Stack (x ': xs)) where 
    showsPrec d (Push x xs) = showParen (d > 10) $ 
     showString "Push " . showsPrec 11 x . showChar ' ' . showsPrec 11 xs 

instance Eq (Stack '[]) where 
    _ == _ = True 

instance (Eq x, Eq (Stack xs)) => Eq (Stack (x ': xs)) where 
    (Push x xs) == (Push y ys) = x == y && xs == ys 

instance Ord (Stack '[]) where 
    compare _ _ = EQ 

instance (Ord x, Ord (Stack xs)) => Ord (Stack (x ': xs)) where 
    compare (Push x xs) (Push y ys) = case compare x y of 
    EQ -> compare xs ys 
    LT -> LT 
    GT -> GT 


push :: x -> Stack xs -> Stack (x ': xs) 
push = Push 

pop :: Stack (x ': xs) -> Stack xs 
pop (Push _ xs) = xs 

top :: Stack (x ': xs) -> x 
top (Push x _) = x 

empty :: Stack '[] 
empty = Empty 

在ghci中有幾個用途是這樣的:

[1 of 1] Compiling Stack   (typelist.hs, interpreted) 
Ok, modules loaded: Stack. 
*Stack> :t push True . push (Just 'X') . push 5 . push "nil" $ empty 
push True . push (Just 'X') . push 5 . push "nil" $ empty 
    :: Num x => Stack '[Bool, Maybe Char, x, [Char]] 
*Stack> push True . push (Just 'X') . push 5 . push "nil" $ empty 
Push True (Push (Just 'X') (Push 5 (Push "nil" Empty))) 
*Stack> pop . push True . push (Just 'X') . push 5 . push "nil" $ empty 
Push (Just 'X') (Push 5 (Push "nil" Empty)) 
*Stack> pop empty 

<interactive>:75:5: 
    Couldn't match type ‘'[]’ with ‘x0 : xs’ 
    Expected type: Stack (x0 : xs) 
     Actual type: Stack '[] 
    Relevant bindings include 
     it :: Stack xs (bound at <interactive>:75:1) 
    In the first argument of ‘pop’, namely ‘empty’ 
    In the expression: pop empty 

注意,這表示有不錯的功能,在空堆棧上調用poptop時出現編譯時錯誤。但是,要處理起來有點難,因爲你總是需要證明你用非空棧來調用它。這對於防止錯誤很有用,但有時需要更多簿記來說服編譯器說明它是正確的。這種表示方式不是一個好的選擇。這取決於用例。

+0

謝謝!這是一個相當驚人的實現! – 2014-11-23 07:21:37

+0

如果我也能夠爲這個堆棧包含get函數,那將是完美的。給定一個整數i和一個堆棧s,get會返回s的第i個元素。我希望我能夠在推動,彈出和頂部排序後自己做到這一點,但我仍然無法做到。有關這個的任何想法? – 2014-11-23 07:58:18

+0

@ shivanker.goel這個東西很容易被這個實現管理。如果只在編譯時確定索引,這並不是什麼壞事,但如果可以在運行時選擇索引,這是非常困難的。那時,這在Haskell中基本上不可行。 – Carl 2014-11-23 17:47:47

1

您應該無法在空元組上定義pop,但如果我們使用類型類來表示堆棧類型的情況,那麼其餘部分就足夠平滑。

class Stack h where 
    push :: a -> h x -> h (a, x) 
    pop :: h (a, x) -> (h x, a) 
    top :: h (a, x) -> (h (a, x), a) 
    top hax = let (_, a) = pop hax in (hax, a) 

newtype S x = S x 

instance Stack S where 
    push a (S x) = S (a, x) 
    pop (S (a, x)) = (S x, a) 

如果暴露抽象隨着

sempty :: S() 
sempty = S() 

推/流行/頂部和S可以確保沒有人可以建立病理堆棧。如果你對GADTs沒問題,那麼有更好的編碼。

data S h where 
    Nil :: S() 
    Cons :: a -> S x -> S (a, x) 

您可以直接公開此GADT,因爲它已經不能違反類型。

instance Stack S where 
    push = Cons 
    pop (Cons a x) = (x, a) 
+0

感謝您的回答! :) – 2014-11-23 07:21:11

+0

這將是完美的,如果我也能夠包括這個堆棧的get函數。給定一個整數i和一個堆棧s,get會返回s的第i個元素。我希望我能夠在推動,彈出和頂部排序後自己做到這一點,但我仍然無法做到。有關這個的任何想法? – 2014-11-23 15:03:09