Re: [Haskell-cafe] Type classes question

2008-10-07 Thread Ryan Ingram
On Tue, Oct 7, 2008 at 1:13 PM, Roly Perera
[EMAIL PROTECTED] wrote:
 Hi,

 I'm reasonably well versed in Haskell but fairly new to defining type classes.
 In particular I don't really understand how to arrange for all instances of X
 to also be instances of Y.

 It's quite possibly that my question is ill-posed, so I'll make it as concrete
 as possible: in the following code, I define a Stream class, with two
 instances, Stream1 and Stream2.  How do I arrange for there to be one
 implementation of Functor's fmap for all Stream instances?  I currently rely 
 on
 delegation, but in the general case this isn't nice.

With your current implementation, you can't.  You get lucky because
all of your instance declarations are of the form
 instance Stream (X a) a
for some type X.

But it's just as possible to say

 newtype Stream3 = S3 [Int]

 instance Stream Stream3 Int where
   first (S3 xs) = head xs
   next (S3 xs) = tail xs
   fby x (S3 xs) = S3 (x:xs)

Now the only valid fmap_ is over functions of type (Int - Int).

If you really want all your instances to be type constructors, you
should just say so:

 class Stream f where
first :: f a - a
next :: f a - f a
fby :: a - f a - f a

Now, with this implementation what you want is at least somewhat
possible, but there's a new problem: there's no good way in haskell to
define superclasses or default methods for existing classes.  There is
a standing class aliases proposal [1], but nobody has implemented
it.

The current recommended practice is to define a default and leave it
to your instances to use it.  It's kind of ugly, but thems the breaks:

 class Functor f = Stream f where -- you said you want all streams to be 
 functors, so enforce it!
first :: f a - a
next :: f a - f a
fby :: a - f a - f a

 fmapStreamDefault f = uncurry fby . both (f . first) (fmap_ f . next)

 instance Functor Stream1 where fmap = fmapStreamDefault
 instance Stream Stream1 where
first (x : _) = x
next (_ : xs) = xs
fby = (:)

Here's another possible solution:

 newtype AsFunctor s a = AF { fstream :: (s a) }
 instance (Stream f) = Functor (AsFunctor f) where
 fmap f (AF s) = AF (fmapStreamDefault f s)

Now to use fmap you wrap in AF and unwrap with fstream.

None of the existing solutions are really satisfactory, unfortunately.

   -- ryan

[1] http://repetae.net/recent/out/classalias.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type classes question

2008-10-07 Thread Roly Perera
Hi,

I'm reasonably well versed in Haskell but fairly new to defining type classes.  
In particular I don't really understand how to arrange for all instances of X 
to also be instances of Y.  

It's quite possibly that my question is ill-posed, so I'll make it as concrete 
as possible: in the following code, I define a Stream class, with two 
instances, Stream1 and Stream2.  How do I arrange for there to be one 
implementation of Functor's fmap for all Stream instances?  I currently rely on 
delegation, but in the general case this isn't nice.

I guess I'm either misunderstanding what it is I'm trying to achieve, or how to 
do this kind of thing in Haskell.  Any help would be greatly appreciated.

many thanks,
Roly Perera



{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, 
ExistentialQuantification, FunctionalDependencies #-}

module Test where

---
-- Just some helpers.
---

-- Product map.
prod :: (a - b) - (c - d) - (a, c) - (b, d)
f `prod` g = \(a, c) - (f a, g c)

-- Diagonal.
diag :: a - (a, a)
diag x = (x, x)

-- Mediating morphism into the product.
both :: (a - b) - (a - c) - a - (b, c)
both f g = prod f g . diag

---
-- Abstract stream.
---
class Stream s a | s - a where
first :: s - a
next :: s - s
fby :: a - s - s

-- I want every Stream to be a Functor.
fmap_ :: Stream s' b = (a - b) - s - s'
fmap_ f = uncurry fby . both (f . first) (fmap_ f . next)

---
-- Implementation 1.
---
data Stream1 a = a : Stream1 a

instance Functor Stream1 where
fmap = fmap_

instance Stream (Stream1 a) a where
first (x : _) = x
next (_ : xs) = xs
fby = (:)

---
-- Implementation 2.
---
data Stream2 a = forall b . S b (b - a) (b - b)

instance Functor Stream2 where
fmap = fmap_

instance Stream (Stream2 a) a where
first (S x c _) = c x
next (S x c i) = S (i x) c i
fby y s = S (y, s) fst (uncurry (,) . both first next . snd)




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type classes question

2008-10-07 Thread Bulat Ziganshin
Hello Roly,

Tuesday, October 7, 2008, 4:13:25 PM, you wrote:

 I'm reasonably well versed in Haskell but fairly new to defining type classes.

http://haskell.org/haskellwiki/OOP_vs_type_classes may be useful

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe