[Haskell-cafe] specifying using type class

Alejandro Serrano Mena trupill at gmail.com
Mon Jul 23 11:31:13 CEST 2012


I don't know whether this is really applicable but: isn't emptyStack in
Ertugrul last message some kind of constructor? You can add any kind of
special constructors as functions in the type class which return a new
queue. For example:

class Stack s where
  newEmptyStack :: s a
  newSingletonStack :: a -> s a
  ...

Why doesn't this fulfill you needs of specifying ways to construct new
elements?

2012/7/23 Patrick Browne <patrick.browne at dit.ie>

>
>
> On 22/07/12, *Ertugrul Söylemez * <es at ertes.de> wrote:
>
>
>
> 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:
>
>
>
> No really. I am investigating the strengths and weaknesses of type classes
> as a *unit of specification*.
> I am aware that their primarily intended to act as interface description,
> which I suppose is a form of specification.
> To what degree could the QUEUE_SPEC (repeated below) from my first posting
> be expressed as a type class?
> From the feedback, I get the impression that an abstract specification
> such as QUEUE_SPEC cannot be expressed as a type class (as an instance yes).
> The stumbling block seems to be the abstract representation of
> constructors.
> In [1]  the classes Moveable and Named are combined, but again each of
> these classes are pure signatures.
>
> Regards,
> Pat
> [1]Haskell: The Craft of Functional Programming (Second Edition) Simon
> Thompson, page 270
>
>
>
> module QUEUE_SPEC where
> data Queue e   = New | Insert (Queue e) e deriving Show
>
> isEmpty :: Queue  e  -> Bool
> isEmpty  New  = True
> isEmpty (Insert q e) = False
>
> first :: Queue  e  -> e
> first (Insert q e) =  if (isEmpty q) then e else (first q)
>
>
> rest :: Queue  e  -> Queue  e
> rest (Insert  q e ) = if (isEmpty q) then New  else (Insert (rest q) e)
>
>
> size :: Queue  e  -> Int
> size New  = 0
> size (Insert q e) = succ (size q)
>
> {-
> some tests of above code
> size (Insert (Insert (Insert New 5) 6) 3)
> rest (Insert (Insert (Insert New 5) 6) 3)
>
>
>
> 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
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120723/7e8d360e/attachment.htm>


More information about the Haskell-Cafe mailing list