2014-11-22 49 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