Ertugrul ,
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



On 22/07/12, Ertugrul Söylemez <es@ertes.de> wrote:
Patrick Browne <patrick.browne@dit.ie> wrote:

> {-
> Below is a *specification* of a queue.
> If possible I would like to write the equations in type class.
> Does the type class need two type variables?
> How do I represent the constructors?
> Can the equations be written in the type class rather than the
> instance? -}

(Side note:  When opening a new topic, please don't /reply/ to a post,
but post it separately by creating a new mail.)

The type class needs to know the element type, so your observation is
correct.  Usually, as in your case, the element type follows from the
data structure type, and you will want to inform the type system about
this connection.  There are basically three ways to do it.  The first is
using MultiParamTypeClasses and FunctionalDependencies:

    class Stacklike a s | s -> a where
        empty :: s a
        null  :: s a -> Bool
        push  :: a -> s a -> s a
        pop   :: s a -> Maybe a
        size  :: s a -> Int
        tail  :: s a -> Maybe (s a)

Another way is using an associated type (TypeFamilies).  This is
cleaner, but much more noisy in the type signatures:

    class Stacklike s where
        type StackElement s

        empty :: s (StackElement s)
        null  :: s (StackElement s) -> Bool
        push  :: StackElement s -> s (StackElement s) -> s (StackElement s)
        pop   :: s (StackElement s) -> Maybe (StackElement s)
        size  :: s (StackElement s) -> Int
        tail  :: s (StackElement s) -> Maybe (s (StackElement s))

Finally once you realize that there is really no need to fix the element
type in the type class itself, you can simply write a type class for the
type constructor, similar to how classes like Functor are defined:

    class Stacklike s where
        empty :: s a
        null  :: s a -> Bool
        push  :: a -> s a -> s a
        pop   :: s a -> Maybe a
        size  :: s a -> Int
        tail  :: s a -> Maybe (s a)

The big question is whether you want to write a class at all.  Usually
classes are used to capture patterns, not operations.


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.

Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán. http://www.dit.ie
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie