Constructor class

2001-10-18 Thread Tom Pledger

Raul Sierra writes:
 | Hi all,
 | 
 | What is the difference between regular classes and constructor classes
 | and how do you specify  that a class is a constructor class?
 | 
 | Thanks in advance,
 | Raul

The term `constructor class' is meant to include classes like Functor
and Monad, whose instances are type constructors but not types.

instance Functor Maybe where ...  -- OK, and Functor is a constructor class
foo :: Maybe  -- Error, because Maybe isn't a type

instance Eq () where ...  -- OK, and Eq is a type class
bar :: () -- OK, because () is a type

There's no particular syntax to distinguish constructor classes from
type classes.  It's inferred from the method signatures.

class Functor f where
fmap :: (a -> b) -> (f a -> f b)
-- Here f's kind is inferred as *->* (unary type constructor)

class Eq a where
(==), (/=) :: a -> a -> Bool
-- Here a's kind is inferred as * (nullary type constructor, or type)

Here's a previous thread about kind inference, if you're interested.
http://haskell.cs.yale.edu/pipermail/haskell/2001-February/000489.html

Regards,
Tom

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Constructor class

2001-10-18 Thread Raul Sierra

Hi all,

What is the difference between regular classes and constructor classes
and how do you specify  that a class is a constructor class?

Thanks in advance,
Raul

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: constructor class & data constructor context

1999-03-02 Thread Lennart Augustsson


>   data (Num a)  => Rsi a = Rsi a a
>   data (Integral a) => Rse a = Rse a a
Contexts on data declarations in Haskell essentially pointless.
Just remove them and figure out how to make your code
work without them, since they don't do anything.

 -- Lennart





constructor class & data constructor context

1999-03-02 Thread S.D.Mechveliani

Dear people,

i cannot tell, whether the following is a particular implementation
bug or it is against Haskell-98:

  class Rs r where  toRs :: r a -> a -> r a

  data (Num a)  => Rsi a = Rsi a a
  data (Integral a) => Rse a = Rse a a

  instance Rs Rsi where  toRs (Rsi _ b) a = Rsi (a-b) b
  instance Rs Rse where  toRs (Rse _ b) a = Rse (rem a b) b

It wants to say, that  toRs  implements differently for several
constructors.
As Rsi is declared to presume the  Num a  context,
has Haskell to accept `a-b' in the instance for Rsi ?

If it has not, then this reduces the language expressiveness ...
How to fix this?

Thank you in advance.


--
Sergey Mechveliani
[EMAIL PROTECTED]





Fwd: Re: tuple selector could be useful + constructor class problems

1997-02-01 Thread David J. King


[This is a re-post of an article from "Thomas Hallgren" that many mail
systems threw back at me.  I'm still not sure what the problem was,
but I'm trying a resend without the mime-encoding.  -- David ]


--- Forwarded Message

Date: Thu, 30 Jan 1997 23:33:00 +0100
From: Thomas Hallgren at home <[EMAIL PROTECTED]>
To: [EMAIL PROTECTED]
Subject: Re: tuple selector could be useful + constructor class problems


Christoph Herrmann wrote:
> I always find it annoying to have a lot of
> auxiliary functions for selecting elements of
> tuples. It would be nice to have, e.g.,
> an infix operator, say "#", that takes a tuple
> and an integer >constant< and delivers one element
> out of the tuple

You can (almost) do this with Haskell 1.3 constructor classes. I enclose
a module that gives you overloaded selector functions called part1,
part2, part3, and so on, that work on all tuples sizes (upto an
arbitrary limit, in the enclosed code chosen to be 4 :-).

However, because the way constructor classes work in Haskell 1.3, it only
almost works. For instance, I had to number the parts from right to left
to get it to work. So, this turns out to be a good example where the rather
annoying restrictions (or lack of expressiveness) that constructor classes
have, pop up. Two problem are:

1. If "T a b" is a type, then the type constructor "\ b -> T a b"  can be
expressed as "T a", but the type constructor "\ a -> T a b" CAN NOT be
expressed. This severely restricts the ways in which the same type can
be declared an instance of different constructor classes and is the reason
why I had to number the parts from right to left to get the selector
functions to work.

2. Classes can only be related in the subclass hierarchy if they work on
type constructors of the same kind. For example, the Monad class is for
types of kind *->*. State monads would have an extra parameter in the
type, so a class StateMonad would be for types of kind *->*->*. This
means that StateMonad can not be a subclass of Monad, which otherwise
seems very natural. Also, without this relationship, types of the form
"(Monad (m s),StateMonad m) => ...", which are currently illegal in
Haskell, would easily arise, I presume. The same problem occurs in my
selector function solution in the type of functions like

swaparound t = (part1 t,part2 t, part3 t)

If problems like these are solved, then the problem of selector
functions is solved too, or at least reduced to a minor practical issue.

(And while I am at it...) It would of course also be nice to have proper
record types with subtyping. This would provide the most general and
convenient solution to the selector function problem, I suppose. Isn't
it about time record types with subtyping were integrated into widely
used functional languages? The type inference problem has been solved
many times over by now (see, e.g., Didier Remy's Projective ML), hasn't
it? A problem then is how subtyping should be integrated with the
Haskell class system. Wouldn't it be really great if someone solved
that!

Thomas H


module TupleSelectors where

-- Classes for tuple component selectors.
-- Note: parts are numbered from right to left.

-- Size 2 tuples --

class Tuple2 p where
  part2 :: p a b -> a
  part1 :: p a b -> b

instance Tuple2 (,) where
  part2 (a,b) = a
  part1 (a,b) = b

-- Size 3 tuples --

class Tuple3 t where
  part3 :: t a b c -> a

instance Tuple3 (,,) where
  part3 (a,b,c) = a

instance Tuple2 ((,,) a) where
  part1 (a,b,c) = c
  part2 (a,b,c) = b

-- Size 4 tuples --

class Tuple4 q where
  part4 :: q a b c d -> a

instance Tuple4 (,,,) where
  part4 (a,b,c,d) = a

instance Tuple3 ((,,,) a) where
  part3 (a,b,c,d) = b

instance Tuple2 ((,,,) a b) where
  part2 (a,b,c,d) = c
  part1 (a,b,c,d) = d

-- and so on for other sizes...


module TestSelectors where
import TupleSelectors

p = ("Hej",False)

p1p = part1 p
p2p = part2 p

-- p3p = part3 p -- type error

t = ("Hej",False,not)

p1t = part1 t
p2t = part2 t
p3t = part3 t

q = ("Hej",False,not,())

p1q = part1 q
p2q = part2 q
p3q = part3 q
p4q = part4 q

swaparound t = (part1 t,part2 t, part3 t)
   -- type inference problems (context reduction problems)



--- End of Forwarded Message











Re: tuple selector could be useful + constructor class problems

1997-01-31 Thread Benedict R. Gaster


Hi,

Thomas Hallgren writes:

> You can (almost) do this with Haskell 1.3 constructor classes. I enclose
> a module that gives you overloaded selector functions called part1,
> part2, part3, and so on, that work on all tuples sizes (up to an
> arbitrary limit, in the enclosed code chosen to be 4 :-).

> However, because the way constructor classes work in Haskell 1.3, it only
> almost works. For instance, I had to number the parts from right to left
> to get it to work. So, this turns out to be a good example where the rather
> annoying restrictions (or lack of expressiveness) that constructor classes
> have, pop up. Two problem are:

If you were prepared to use the records of Haskell 1.3 this problem could be
resolved simply by the fact that field ordering is arbitrary. Consider,
for example the following Haskell datatypes:

data Point = MkP {xP :: Int, yP :: Int}

data CPoint = MkCp {colour :: Bool, xCp :: Int, yCp :: Int}

Now using the same idea as Thomas we can define a class for selecting an
x component from a given record as:

class FieldX a where
x :: a -> Int

and two instances of this class, one for each of the datatype definitions.

instance FieldX Point where
x = xP

instance FieldX CPoint where
x = xCp

One important point concerns the result type of the member function x, which
has been fixed to Int, and thus, restricts the overloading of selector functions
to a fixed result type. There are a number of possible solutions to this 
problem, the most obvious is to extend Haskell classes to multi-parameter.

> (And while I am at it...) It would of course also be nice to have proper
> record types with subtyping. This would provide the most general and
> convenient solution to the selector function problem, I suppose. Isn't
> it about time record types with subtyping were integrated into widely
> used functional languages? 


It is hard to know exactly what is meant by record types and subtyping, in
that extensible records provide a form of subtyping corresponding to simple
inheritance models for object-oriented. For example, consider types for points
and colour points: 

type Point  = Rec {x:: Int, y :: Int}

type CPoint = Rec {colour :: Bool | Point},

where CPoint is defined simply as a Point type extended with an additional
field colour. The subtyping relationship between Point and CPoint can be
highlighted by considering a function to retrieve the x component of either
a point or colour point:

getX r = r.x

which in a system supporting extensible records might be assigned the type:

Rec {x :: a | r} ->  a,

where ranges over all fields except x. Thus, the subtyping relationship 
between Point and CPoint can be defined as:

CPoint < Point,

which asserts that CPoint contains at least all the fields present in Point.

The form of subtyping described above is weaker that the more general notion 
proposed by Mitchell [Mit91], in which subtyping constraints over a variety
of different types, and the general notion of solving these constraints are
considered.

> The type inference problem has been solved
> many times over by now (see, e.g., Didier Remy's Projective ML), hasn't
> it? A problem then is how subtyping should be integrated with the
> Haskell class system. Wouldn't it be really great if someone solved
> that!

If subtyping is considered as above, then Mark Jones and myself have a paper
[GJ96] describing a type system for polymorphic extensible records as an
application of qualified types, which may be integrated directly into the 
Haskell type system.

Many regards

Ben

@article{Mit91,
author  = "John C. Mitchell",
title   = "Type inference with simple subtypes",
journal = "Journal of Functional Programming",
year= "1991",
volume  = "1",
number  = "3",
pages   = "245-285",
month   = "July"}

@techreport(GJ96,
author   = "Benedict R. Gaster and Mark P. Jones",
title= "A Polymorphic Type System for Extensible Records and Variants",
institution  = "Computer Science, University of Nottingham",
year = "1996",
month= "November",
type = "Technical Report" ,
number   = "NOTTCS-TR-96-3")


Benedict R. Gaster.
Functional Programming Group, Nottingham University.
Category theory: This is how our children will program!

--
[Moderator's note: If you did not receive the post that this is a
reply to, and would like it, then mail <[EMAIL PROTECTED]> with
"resend tuple mail" in the subject line.  We have had DNS problems at
Glasgow.]





Re: tuple selector could be useful + constructor class problems

1997-01-30 Thread Thomas Hallgren at home

--15FB7483794BDF32446B9B3D
Content-Type: text/plain; charset="us-ascii"

Christoph Herrmann wrote:
> I always find it annoying to have a lot of
> auxiliary functions for selecting elements of
> tuples. It would be nice to have, e.g.,
> an infix operator, say "#", that takes a tuple
> and an integer >constant< and delivers one element
> out of the tuple

You can (almost) do this with Haskell 1.3 constructor classes. I enclose
a module that gives you overloaded selector functions called part1,
part2, part3, and so on, that work on all tuples sizes (upto an
arbitrary limit, in the enclosed code chosen to be 4 :-).

However, because the way constructor classes work in Haskell 1.3, it only
almost works. For instance, I had to number the parts from right to left
to get it to work. So, this turns out to be a good example where the rather
annoying restrictions (or lack of expressiveness) that constructor classes
have, pop up. Two problem are:

1. If "T a b" is a type, then the type constructor "\ b -> T a b"  can be
expressed as "T a", but the type constructor "\ a -> T a b" CAN NOT be
expressed. This severely restricts the ways in which the same type can
be declared an instance of different constructor classes and is the reason
why I had to number the parts from right to left to get the selector
functions to work.

2. Classes can only be related in the subclass hierarchy if they work on
type constructors of the same kind. For example, the Monad class is for
types of kind *->*. State monads would have an extra parameter in the
type, so a class StateMonad would be for types of kind *->*->*. This
means that StateMonad can not be a subclass of Monad, which otherwise
seems very natural. Also, without this relationship, types of the form
"(Monad (m s),StateMonad m) => ...", which are currently illegal in
Haskell, would easily arise, I presume. The same problem occurs in my
selector function solution in the type of functions like

swaparound t = (part1 t,part2 t, part3 t)

If problems like these are solved, then the problem of selector
functions is solved too, or at least reduced to a minor practical issue.

(And while I am at it...) It would of course also be nice to have proper
record types with subtyping. This would provide the most general and
convenient solution to the selector function problem, I suppose. Isn't
it about time record types with subtyping were integrated into widely
used functional languages? The type inference problem has been solved
many times over by now (see, e.g., Didier Remy's Projective ML), hasn't
it? A problem then is how subtyping should be integrated with the
Haskell class system. Wouldn't it be really great if someone solved
that!

Thomas H

--15FB7483794BDF32446B9B3D
Content-Disposition: inline; filename="TupleSelectors.hs"
Content-Type: text/plain; charset="us-ascii"; name="TupleSelectors.hs"

module TupleSelectors where

-- Classes for tuple component selectors.
-- Note: parts are numbered from right to left.

-- Size 2 tuples --

class Tuple2 p where
  part2 :: p a b -> a
  part1 :: p a b -> b

instance Tuple2 (,) where
  part2 (a,b) = a
  part1 (a,b) = b

-- Size 3 tuples --

class Tuple3 t where
  part3 :: t a b c -> a

instance Tuple3 (,,) where
  part3 (a,b,c) = a

instance Tuple2 ((,,) a) where
  part1 (a,b,c) = c
  part2 (a,b,c) = b

-- Size 4 tuples --

class Tuple4 q where
  part4 :: q a b c d -> a

instance Tuple4 (,,,) where
  part4 (a,b,c,d) = a

instance Tuple3 ((,,,) a) where
  part3 (a,b,c,d) = b

instance Tuple2 ((,,,) a b) where
  part2 (a,b,c,d) = c
  part1 (a,b,c,d) = d

-- and so on for other sizes...

--15FB7483794BDF32446B9B3D
Content-Disposition: inline; filename="TestSelectors.hs"
Content-Type: text/plain; charset="us-ascii"; name="TestSelectors.hs"

module TestSelectors where
import TupleSelectors

p = ("Hej",False)

p1p = part1 p
p2p = part2 p

-- p3p = part3 p -- type error

t = ("Hej",False,not)

p1t = part1 t
p2t = part2 t
p3t = part3 t

q = ("Hej",False,not,())

p1q = part1 q
p2q = part2 q
p3q = part3 q
p4q = part4 q

swaparound t = (part1 t,part2 t, part3 t)
   -- type inference problems (context reduction problems)


--15FB7483794BDF32446B9B3D--