Re: Arrow Classes

2003-07-15 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote:

 It doesn't provide instances of Num for anything which is already an instance 
 of the other classes. And in Haskell 98 they must be defined separately for 
 each type, instance (...) = Num a doesn't work.

It works in extended Haskell however, so I suspect it lays to rest the 
question of needing some other language extension.

-- 
Ashley Yakeley, Seattle WA

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


Re: Arrow Classes

2003-07-15 Thread Dylan Thurston
On Tue, Jul 15, 2003 at 01:07:12AM -0700, Ashley Yakeley wrote:
 In article [EMAIL PROTECTED],
  Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote:
 
  It doesn't provide instances of Num for anything which is already an instance 
  of the other classes. And in Haskell 98 they must be defined separately for 
  each type, instance (...) = Num a doesn't work.
 
 It works in extended Haskell however, so I suspect it lays to rest the 
 question of needing some other language extension.

I disagree!  This method (putting each function in its own class) does
not address two related points:

a) Being able to declare default values for a method declared in a
superclass;

b) Being able to refine a type heirarchy without the users noticing
(and without explosion of the number of instance declarations
required).

Peace,
Dylan


pgp0.pgp
Description: PGP signature


Re: Arrow Classes

2003-07-14 Thread Graham Klyne
At 10:58 12/07/03 +0100, Alastair Reid wrote:
we could have 'context synonyms' like:

  class Num a = (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...)

Adding context synonyms would make it possible to write types concisely when
using fine-grained class hierarchies and would also be useful with extensions
like Hugs' T-REX or implicit parameters.
I must be missing something... isn't the effect achieved by:

  class (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) = Num a

?

I guess it would be nice if declaring an instance of Num could specify the 
methods for Add, Subtract, etc...), but that seems a small thing, and I'm 
not sure it wouldn't introduce other problems.

#g

---
Graham Klyne
[EMAIL PROTECTED]
PGP: 0FAA 69FF C083 000B A2E9  A131 01B9 1C7A DBCA CB5E
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Arrow Classes

2003-07-12 Thread Alastair Reid

 I'm glad to hear there isn't a _serious_ cost (i.e. performance penalty)
 for fine-grained hierarchies. 

One cost which doesn't seem to have been mentioned is the programmer cost. 

With the current Haskell Prelude, a matrix operation (say) might have type:

  invert :: Num a = Matrix a - Matrix a

but, if we had one operation per class, the type might be:

  invert :: (Add a, Subtract a, FromInteger a, Eq a, Multiply a) 
 = Matrix a - Matrix a

More flexible but quite unwieldy.


One way to overcome part of this problem would be to generalize the idea of 
'type synonyms' to allow 'context synonyms'.  For example, we have type 
synonyms like:

  type Point = (Int,Int)

we could have 'context synonyms' like:

  class Num a = (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) 

Adding context synonyms would make it possible to write types concisely when 
using fine-grained class hierarchies and would also be useful with extensions 
like Hugs' T-REX or implicit parameters.


Adding context synonyms would not help with type error messages though.  When 
using TREX to encode an abstract syntax tree for the C language, I once got 
an error message that was over two pages long (i.e., about 4000 characters 
long).  The error message amounted to saying that one list of fields didn't 
match another list of fields but with two pages of field names to look at, it 
was impossible to say what the differences between the types were.  Things 
would not be that bad with the example types above but they would certainly 
be harder than  the current error messages.

--
Alastair Reid




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


Re: Arrow Classes

2003-07-12 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Alastair Reid [EMAIL PROTECTED] wrote:

 One way to overcome part of this problem would be to generalize the idea of 
 'type synonyms' to allow 'context synonyms'.  For example, we have type 
 synonyms like:
 
   type Point = (Int,Int)
 
 we could have 'context synonyms' like:
 
   class Num a = (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) 

That would be quite unnecessary. Simply write this:

  class (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) =
   Num a;
  instance (Add a, Subtract a, FromInteger a, Eq a, Multiply a, ...) =
   Num a;

And now you can write this:

  invert :: Num a = Matrix a - Matrix a

I use this idiom quite frequently for joining classes together.

-- 
Ashley Yakeley, Seattle WA

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


Re: Arrow Classes

2003-07-10 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Ross Paterson [EMAIL PROTECTED] wrote:

 The point about symmetry is a fair one, but unfortunately the Haskell class
 system imposes a cost on fine-grained class hierarchies, 

It does?

-- 
Ashley Yakeley, Seattle WA

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


Re: Arrow Classes

2003-07-10 Thread Ross Paterson
On Thu, Jul 10, 2003 at 02:00:37AM -0700, Ashley Yakeley wrote:
 In article [EMAIL PROTECTED],
  Ross Paterson [EMAIL PROTECTED] wrote:
 
  The point about symmetry is a fair one, but unfortunately the Haskell class
  system imposes a cost on fine-grained class hierarchies, 
 
 It does?

There are more instances and methods for people to define, even if some
of them imply others.

As it happens, I would like yet another intermediate class:

class BiFunctor a where
bimap :: (b' - b) - (c - c') - a b c - a b' c'

(and I have a client for the class: a useful subset of the arrow notation
needs only this, in fact only the contravariant part.)

Clearly any arrow is also an instance of this class:

bimap b c f = arr b  f  arr c

but you still have to define bimap even if the type is also an arrow.

Subclasses in Haskell cover a range of relationships, including this
sense where things in the subclass automatically belong to the superclass.
Other examples include Eq = Ord and Functor vs Monad.  In such cases it
would be handy if the subclass could define defaults for the superclass
methods (e.g. Ord defining (==)), so that the superclass instance could
be optional.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Arrow Classes

2003-07-10 Thread Wolfgang Jeltsch
On Thursday, 2003-07-10, 15:33, Ross Paterson wrote:
 [...]

 There are more instances and methods for people to define, even if some of
 them imply others.

 As it happens, I would like yet another intermediate class:

   class BiFunctor a where
   bimap :: (b' - b) - (c - c') - a b c - a b' c'

 (and I have a client for the class: a useful subset of the arrow notation
 needs only this, in fact only the contravariant part.)

 Clearly any arrow is also an instance of this class:

   bimap b c f = arr b  f  arr c

 but you still have to define bimap even if the type is also an arrow.

 Subclasses in Haskell cover a range of relationships, including this sense
 where things in the subclass automatically belong to the superclass. Other
 examples include Eq = Ord and Functor vs Monad.  In such cases it would be
 handy if the subclass could define defaults for the superclass methods (e.g.
 Ord defining (==)), so that the superclass instance could be optional.

Exactly. Maybe, the problem is not the existence of many classes but the lack 
of such an defaults for superclass methods feature.

Wolfgang

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


Re: Arrow Classes

2003-07-10 Thread Wolfgang Jeltsch
On Thursday, 2003-07-10, 15:33, Ross Paterson wrote:
 [...]

 Subclasses in Haskell cover a range of relationships, including this sense
 where things in the subclass automatically belong to the superclass. Other
 examples include Eq = Ord and Functor vs Monad.

By the way, I strongly vote for Functor being a superclass of Monad in Haskell 
2.

 [...]

Wolfgang

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


Re: Arrow Classes

2003-07-10 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Wolfgang Jeltsch [EMAIL PROTECTED] wrote:

 By the way, I strongly vote for Functor being a superclass of Monad in 
 Haskell 2.

I recently created my own Monad class in HBase instead of using the 
Prelude one. The hierarchy looks something like this:

  class HasReturn f where
   return :: a - f a

  class Functor f where
   fmap :: (a - b) - f a - f b

  class (Functor f) = FunctorApply f where
   fApply :: f (a - b) - f a - f b
   fPassTo :: f a - f (a - b) - f b
   () :: f a - f b - f b

  class (FunctorApply f,HasReturn f) = FunctorApplyReturn f
  instance (FunctorApply f,HasReturn f) = FunctorApplyReturn f

  class (FunctorApplyReturn f) =
   Monad f where
   (=) :: f a - (a - f b) - f b

  class (Functor f) =
   ExtractableFunctor f where
   fExtract :: (FunctorApplyReturn g) = f (g a) - g (f a)
   fToList :: f a - [a] -- has default definition (exercise for the 
reader)

Certain standard monadic functions, such as LiftM2, actually apply to 
classes higher up the hierarchy (FunctorApply, in this case). 
FunctorApplyReturn is a particularly useful class for manipulating 
things in a box when the box isn't quite a Monad.

I'm glad to hear there isn't a _serious_ cost (i.e. performance penalty) 
for fine-grained hierarchies. Yeah, so if you want to define your own 
Monad, you have to define all the other instances too. I ease this by 
providing functions such as monad_fmap and monad_fApply etc. that you 
can use for your instances.

-- 
Ashley Yakeley, Seattle WA

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


Re: Arrow Classes

2003-07-10 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Ross Paterson [EMAIL PROTECTED] wrote:

 As it happens, I would like yet another intermediate class:
 
   class BiFunctor a where
   bimap :: (b' - b) - (c - c') - a b c - a b' c'

This can be decomposed into:

  fmap :: (c - c') - a b c - a b c'

  cofmap2 :: (b' - b) - a b c - a b' c

  bimap :: (Cofunctor2 a,Functor (a b)) =
   (b' - b) - (c - c') - a b c - a b' c'
  bimap bb cc = (cofmap2 bb) . (fmap cc)

It would be nice to be able to write this:

  class (Cofunctor2 a,forall b. Functor (a b)) =
   BiFunctor a
  instance (Cofunctor2 a,forall b. Functor (a b)) =
   BiFunctor a

Unfortunately, foralls are not allowed in class or instance contexts...

-- 
Ashley Yakeley, Seattle WA

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


Re: Arrow Classes

2003-06-28 Thread Joe English

Ashley Yakeley wrote:
 Wolfgang Jeltsch wrote:

  This brings me to another point. One year ago we had a discussion on The
  Haskell Mailing List concerning arrows. (The subject of the mails was just
  arrows.) The point was that it seemed strange to me that first and second
  are included in the basic arrow class Arrow while left and right have their
  extra class ArrowChoice. Not only that it seemed strange to me but it made
  impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad
  has nice implementations of pure and () but none of first or second.

 I agree. My own Arrow module hierarchy looks more or less like this:

   class Compositor comp where [...]
   class (Compositor arrow) = Arrow arrow where [...]
   class (Arrow arrow) = ProductArrow arrow where [...]
   class (Arrow arrow) = CoproductArrow arrow where [...]
   class (ProductArrow arrow,CoproductArrow arrow) = FullArrow arrow
   instance (ProductArrow arrow,CoproductArrow arrow) = FullArrow arrow
   class (Arrow arrow) = ArrowFix arrow where [...]
   class (FullArrow arrow) = ApplyArrow arrow where [...]


On that topic, see below for what mine looks like
(from HXML, URL: http://www.flightlab.com/~joe/hxml/ ).

I started off with Hughes' conventions, but for some
reason could never remember the difference between  and ***,
or between ||| and +++.  I found , , |||, | to have
better mnemonic value.  This also frees up +++ for ArrowPlus,
which -- in HXML applications -- is frequently used and should
thus be easy to type.

When using the ArrowChoice operators, I kept tripping over all
the 'Either' coproduct types, so added some syntactic sugar
(borrowed from HaXML):

data Choice a = a : a
class (Arrow a) = ArrowChoice a where
[ ... ]
( ?)   :: (b - Bool) - Choice (a b c) - a b c
(?)   :: a b Bool- Choice (a b c) - a b c

I found p ? f : g much more pleasant to use.

(I also like the idea of splitting the product operators out of
the base Arrow class -- will consider doing that in my library).

--

infixr 5 +++
infixr 3 , 
infixr 2 |, |||, ?, ?, :
infixl 1 

class Arrow a where
arr :: (b - c) - a b c
()   :: a b c - a c d - a b d
apfst   :: a b c - a (b,x) (c,x)
apsnd   :: a b c - a (x,b) (x,c)
()   :: a b c - a d e - a (b,d) (c,e)
()   :: a b c - a b d - a b (c,d)
liftA2  :: (b - c - d) - a e b - a e c - a e d
aConst  :: c - a b c
idArrow :: a b b
-- Minimal implementation: arr, ,  apfst or 

data Choice a = a : a
class (Arrow a) = ArrowChoice a where
apl :: a b c - a (Either b d) (Either c d)
apr :: a b c - a (Either d b) (Either d c)
(|)   :: a b c - a d e - a (Either b d) (Either c e)
(|||)   :: a b c - a d c - a (Either b d) c
( ?)   :: (b - Bool) - Choice (a b c) - a b c
(?)   :: a b Bool- Choice (a b c) - a b c
-- Minimal implementation: | or apl

class (Arrow a) = ArrowApply a where
app :: a (a b c,b) c

class (Arrow a) = ArrowZero a where
aZero  :: a b c
aMaybe :: a (Maybe c) c
aGuard :: (b - Bool) - a b b

class (Arrow a) = ArrowPlus a where
(+++) :: a b c - a b c - a b c



--Joe English

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