Re: Re[2]: Tuple-like constructors

2006-02-08 Thread Malcolm Wallace
Robert Dockins [EMAIL PROTECTED] writes:

 instance (Bin a,Bin b,Bin c,Bin d) = Bin (a,b,c,d)
 
 See the problem?  Sooner or later (probably sooner) I'll get tired of  
 typing.  I have to write down an 'instance' declaration for each  
 value of n.  Clearly this can't generalize to all n.

There has been a suggestion that the 'deriving' mechanism be de-coupled
from the datatype declaration.  Together with a generic default
definition, that means you could write something like

deriving Bin for ()

and hence not need to write the tedious instance header yourself,
since the compiler can easily infer it.

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Tuple-like constructors

2006-02-07 Thread Bulat Ziganshin
Hello Robert,

Tuesday, February 07, 2006, 6:42:41 PM, you wrote:

 More disturbing is the complete inability to write general functions
 over tuples.

RD As I understand it, you still have to write down the instance  
RD declarations when using '-fgenerics'.

only one generic instance. it's very much these ideas of using nested
tuples, only with special syntax. below is my definitions of Binary
class for types with only one constructor:

class Binary a where
-- | Convert value to sequence of bits and write it to the stream
put_ :: (BinaryStream m h) = h - a - m ()
-- | Read value written to the stream as bit sequence
get  :: (BinaryStream m h) = h - m a
{-
Using generic type classes extension, GHC allows to semi-automatically
generate instances of Binary for any types. All what you need to define
Binary instance for some type MyType is to write:

instance Binary MyType where

These is the all definitions required, but they don't work
because of current restrictions in GHC's generics support:

put_ {| Unit  |}  h  Unit = return ()
put_ {| a:*:b |}  h (x :*: y) = do put_ h x; put_ h y

get  {| Unit  |}  h = return ()
get  {| a:*:b |}  h = do x - get h; y - get h; return (x :*: y)
-}



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: Tuple-like constructors

2006-02-07 Thread Robert Dockins
On Feb 7, 2006, at 11:29 AM, Bulat Ziganshin wrote:Hello Robert,Tuesday, February 07, 2006, 6:42:41 PM, you wrote: More disturbing is the complete inability to write general functionsover tuples. RD As I understand it, you still have to write down the instance  RD declarations when using '-fgenerics'.only one generic instance. it's very much these ideas of using nestedtuples, only with special syntax. below is my definitions of Binaryclass for types with only one constructor:[snip]To cut an paste from the GHC manual: class Bin a where    toBin   :: a - [Int]    fromBin :: [Int] - (a, [Int])      toBin {| Unit |}    Unit	  = []    toBin {| a :+: b |} (Inl x)   = 0 : toBin x    toBin {| a :+: b |} (Inr y)   = 1 : toBin y    toBin {| a :*: b |} (x :*: y) = toBin x ++ toBin y      fromBin {| Unit |}    bs      = (Unit, bs)    fromBin {| a :+: b |} (0:bs)  = (Inl x, bs')    where (x,bs') = fromBin bs    fromBin {| a :+: b |} (1:bs)  = (Inr y, bs')    where (y,bs') = fromBin bs    fromBin {| a :*: b |} bs	  = (x :*: y, bs'') where (x,bs' ) = fromBin bs			  (y,bs'') = fromBin bs'Now you can make a data type into an instance of Bin like this:  instance (Bin a, Bin b) = Bin (a,b)  instance Bin a = Bin [a]OK. So Now I want a Bin instance for 3-tuples. I have to write down:instance (Bin a, Bin b, Bin c) = Bin (a,b,c)Fine.  Now I want it for 4-tuples instance (Bin a,Bin b,Bin c,Bin d) = Bin (a,b,c,d)See the problem?  Sooner or later (probably sooner) I'll get tired of typing.  I have to write down an 'instance' declaration for each value of n.  Clearly this can't generalize to all n.  So say I'm willing to deal with that and further suppose some super-helpful person writes down all the instances up to n=15 (say) and gets them included in some standard library.  Uh!  Now I discover I need a 17-tuple instance.  OK fine, I have to write down my own special 17-tuple instance.  Suppose (stay with me here), at some later time I import a library written by someone else and they ALSO discovered a need for an instance of this particular class for 17-tuples.  Now our instances overlap!  Double Ugh!  I need to remove one of the instances.Still the problem is that I can't perform type level induction on the shape of the tuple.  However, I'm willing to concede that generics greatly simplifies the problem -- perhaps to the point where my objections are merely academic.OK.  I'm really done now.Rob DockinsSpeak softly and drive a Sherman tank.Laugh hard; it's a long way to the bank.          -- TMBG ___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime