[Haskell-cafe] specifying using type class
Ertugrul Söylemez
es at ertes.de
Sun Jul 22 21:47:59 CEST 2012
Hi there Patrick,
Patrick Browne <patrick.browne at dit.ie> wrote:
> Thanks for you very clear explanation.
> Without committing to some concrete representation such as list I do
> not know how to specify constructors in the class (see below). As you
> point out a class may not be appropriate for an actual application,
> but I am investigating the strengths and weaknesses of class as a unit
> of *specification*. Regards, Pat
>
> -- Class with functional dependency
> class QUEUE_SPEC_CLASS2 a q | q -> a where
> newC2 :: q a -- ??
> sizeC2 :: q a -> Int
> restC2 :: q a -> Maybe (q a)
> insertC2 :: q a -> a -> q a
> -- Without committing to some concrete representation such as list I
> do not know how to specify constructor for insertC2 ?? = ??
> insertC2 newC2 a = newC2 -- wrong isEmptyC2 :: q a -> Bool
> isEmptyC2 newC2 = True
> -- isEmptyC2 (insertC2 newC2 a) = False wrong
You are probably confusing the type class system with something from
OOP. A type class captures a pattern in the way a type is used. The
corresponding concrete representation of that pattern is then written in
the instance definition:
class Stacklike s where
emptyStack :: s a
push :: a -> s a -> s a
rest :: s a -> Maybe (s a)
top :: s a -> Maybe a
pop :: s a -> Maybe (a, s a)
pop s = liftA2 (,) (top s) (rest s)
instance Stacklike [] where
emptyStack = []
push = (:)
top = foldr (\x _ -> Just x) Nothing
rest [] = Nothing
rest (Push _ xs) = Just xs
data MyStack a = Empty | Push a (MyStack a)
instance Stacklike MyStack where
emptyStack = Empty
push = Push
top Empty = Nothing
top (Push x _) = Just x
rest Empty = Nothing
rest (Push _ xs) = Just xs
Greets,
Ertugrul
--
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120722/e6c41066/attachment.pgp>
More information about the Haskell-Cafe
mailing list