RE: [Haskell-cafe] tuples and Show in GHC

2005-03-07 Thread Simon Peyton-Jones
No principled reason.  I wish there was no limit, which would involve
generating code on the fly for instances that weren't pre-generated, but
I never got around to implementing that.  So you have to stop somewhere.
Actually the Report says it should have Show instances up to 15 at
least, but GHC doesn't.  That isn't deliberate, and I guess we should
fix it.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Stijn
| De Saeger
| Sent: 06 March 2005 09:40
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] tuples and Show in GHC
| 
| hi all,
| 
| Is there a principled reason why in GHC tuples with up to five
| elements automatically derive from the Show class but from six
| elements and up they don't anymore? If this is not a bug I would be
| very curious to hear what the reasoning behind this is
| below is an example of said behaviour :
| 
|  type MyInt1 = (Int,Int,Int,Int,Int)
|  myInt1 :: MyInt1
|  myInt1 = (1,2,3,4,5)
|  type MyInt2 = (Int,Int,Int,Int,Int,Int)
|  myInt2 :: MyInt2
|  myInt2 = (1,2,3,4,5,6)
| 
| 
| 
| *HS myInt1
| Loading package haskell98 ... linking ... done.
| (1,2,3,4,5)
| *HS myInt2
| 
| interactive:1:
| No instance for (Show MyInt2)
|   arising from use of `print' at interactive:1
| In a 'do' expression: print it
| *HS
| 
| stijn.
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tuples and Show in GHC

2005-03-07 Thread Remi Turk
On Mon, Mar 07, 2005 at 12:05:41AM +, Keean Schupke wrote:
 Daniel Fischer wrote:
 
 The Show instances for tuples aren't automatically derived, they are 
 defined in GHC.Show. So somewhere there must be an end, probably the 
 author(s) thought that larger tuples than quintuples aren't used often 
 enough to bother. That's not a principled reason but a practical one, but 
 it's good enough for me.
 If you need them frequently and don't want to define your own instances, 
 complain.
 BTW, tuples are defined in Data.Tuple up to 62-tuples and Eq and Ord 
 instances are derived up to 15-tuples.
 In Hugs, apparently they are only provided up to quintuples.
 
 Has there been any work done on declaring instances over all tuples? It 
 seems the pattern occurs fairly often, and is quite simple to abstract.
 
Keean.

Which almost sounds like a hint to replace the current tuples by
HLists in Haskell 2? ;)

Something like:

infixr 5 :*:
data HNil = HNil
data HList b = a :*: b = a :*: !b deriving (Eq, Ord)

-- type () = HNil
type (a,b) = a :*: b :*: HNil
type (a,b,c) = a :*: b :*: c :*: HNil

fst :: HList b = (a :*: b) - a
fst (a:*:b) = a

Where (x,y,z) is syntactic sugar for x :*: y :*: z :*: HNil in
much the same way [x,y,z] is syntactic sugar for x:y:z:[]...

It might even be (almost?) backward compatible AFAICS.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tuples and Show in GHC

2005-03-07 Thread Keean Schupke
Remi Turk wrote:
On Mon, Mar 07, 2005 at 12:05:41AM +, Keean Schupke wrote:
 

Daniel Fischer wrote:
   

The Show instances for tuples aren't automatically derived, they are 
defined in GHC.Show. So somewhere there must be an end, probably the 
author(s) thought that larger tuples than quintuples aren't used often 
enough to bother. That's not a principled reason but a practical one, but 
it's good enough for me.
If you need them frequently and don't want to define your own instances, 
complain.
BTW, tuples are defined in Data.Tuple up to 62-tuples and Eq and Ord 
instances are derived up to 15-tuples.
In Hugs, apparently they are only provided up to quintuples.

 

Has there been any work done on declaring instances over all tuples? It 
seems the pattern occurs fairly often, and is quite simple to abstract.

  Keean.
   

Which almost sounds like a hint to replace the current tuples by
HLists in Haskell 2? ;)
Something like:
infixr 5 :*:
data HNil = HNil
data HList b = a :*: b = a :*: !b deriving (Eq, Ord)
-- type () = HNil
type (a,b) = a :*: b :*: HNil
type (a,b,c) = a :*: b :*: c :*: HNil
fst :: HList b = (a :*: b) - a
fst (a:*:b) = a
Where (x,y,z) is syntactic sugar for x :*: y :*: z :*: HNil in
much the same way [x,y,z] is syntactic sugar for x:y:z:[]...
It might even be (almost?) backward compatible AFAICS.
Groeten,
Remi
 

Whilst thats certainly one way to do it, HLists are composed of binary 
products (,)...  So this
works as long as you can imagine: (a,(b,(c,HNil))) == (a,b,c)

We can define the operations generically using HLists, and we can even 
convert back and
forth from a tuple to an HList (for a limited number of tuple instances).
Infact we might be able to do conversion of arbitrary tuples using 
template-haskell.

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


Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-07 Thread Greg Buchholz
Daniel Fischer wrote:
 Am Freitag, 4. M?rz 2005 19:35 schrieb Greg Buchholz:
  So, can anyone direct me towards more information on exactly
  what an Occurs check is, or does anyone see an easy fix to my
  problems?
 
 If I remember correctly, an occurs check is checking whether a type 
 variable 
 (call it 't') occurs as an argument to a tuple constructor or function arrow 
 in a type expression to be substituted for t, as above or in 
 t = t - t1.
 
 Such occurences would lead to an infinite type, hence are forbidden.

   Interesting, I'll have to think it over. (Of course being a relative
newcomer to Haskell, I have to do a lot of thinking when it comes to
most things.)  BTW, can anyone recommend a good introductory resource
for learning about type theory?  I once flipped through Pierce's
Types_and_Programming_Languages, but at first glance, it seemed to be a
little advanced for my understanding (the foreign-looking equations per
word ratio seemed a little too high).

 I have a fix for the factorial and similar recursive functions, though it's 
 not really easy (and needs extensions):
 don't define the recursion combinators via Stack, do it like this:
 
 linrec2 :: forall a. (forall b. (a,(a,b)) - (a,b)) -
  (forall b. (a,b) - (a,(a,b))) -
(forall b. (a,b) - (a,b)) -
(forall b. (a,b) - (Bool,b)) -
(forall b. (a,b) - (a,b))
 linrec2 rec2 rec1 t p stack
| fst $ p stack = t stack
| otherwise = rec2 $ linrec2 rec2 rec1 t p (rec1 stack)

Nice.  Definitely something for me to study.  Of course, IFAICT, the
main motivation for Joy is to try and define everything in terms of
function composition instead of function application.

 I don't know Joy, but probably there the stack is (roughly) a heterogenous 
 list, which is hard to model in Haskell,

Yeah, I don't know Joy either, other than reading a few documents,
but I do think its stack is really heterogenous list.  The one reason I
was thinking this might be doable in Haskell, is the fact that the few
combinators I looked at don't recurse down the whole stack.  That, of
course, would be a complete nightmare in Haskell.   Instead they take a
stack, munge a few (finite number of) items at the top, and return
another stack.  I was hoping that the type variable a in (Integer,
a) - (Integer, a) would be amorphous enough to match whatever was left
over after grabbing a few items off the top of this stack.

Thanks,

Greg Buchholz

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


Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-07 Thread Daniel Fischer
Am Montag, 7. März 2005 17:58 schrieb Greg Buchholz:
 Daniel Fischer wrote:
  Am Freitag, 4. März 2005 19:35 schrieb Greg Buchholz:
   So, can anyone direct me towards more information on exactly
   what an Occurs check is, or does anyone see an easy fix to my
   problems?
 
  If I remember correctly, an occurs check is checking whether a type
  variable (call it 't') occurs as an argument to a tuple constructor or
  function arrow in a type expression to be substituted for t, as above or
  in
  t = t - t1.
 
  Such occurences would lead to an infinite type, hence are forbidden.

Interesting, I'll have to think it over. (Of course being a relative
 newcomer to Haskell, I have to do a lot of thinking when it comes to
 most things.)  BTW, can anyone recommend a good introductory resource
 for learning about type theory?  I once flipped through Pierce's
 Types_and_Programming_Languages, but at first glance, it seemed to be a
 little advanced for my understanding (the foreign-looking equations per
 word ratio seemed a little too high).

  I have a fix for the factorial and similar recursive functions, though
  it's not really easy (and needs extensions):
  don't define the recursion combinators via Stack, do it like this:
 
  linrec2 :: forall a. (forall b. (a,(a,b)) - (a,b)) -
   (forall b. (a,b) - (a,(a,b))) -
   (forall b. (a,b) - (a,b)) -
   (forall b. (a,b) - (Bool,b)) -
   (forall b. (a,b) - (a,b))
  linrec2 rec2 rec1 t p stack
 
 | fst $ p stack = t stack
 | otherwise = rec2 $ linrec2 rec2 rec1 t p (rec1 stack)

 Nice.  Definitely something for me to study.  Of course, IFAICT, the
 main motivation for Joy is to try and define everything in terms of
 function composition instead of function application.

One more, you need not supply a type signature for fact, if you provide the 
argument:

fact0 (n,st) = ifte (dup ! pre ! fact ! mult, (pop ! lit 1, (nul, (n,st

That's of course rather unJoyful :-), but it helps the type-checker (I don't 
know the workings thereof, but it's often the case that functions which don't 
type-check points-free do if sufficiently many arguments are provided).

I don't think that'll help fact3-5, though.


  I don't know Joy, but probably there the stack is (roughly) a
  heterogenous list, which is hard to model in Haskell,

 Yeah, I don't know Joy either, other than reading a few documents,

I've taken a look, and I must say, I find Haskell more intuitive.

 but I do think its stack is really heterogenous list.  The one reason I
 was thinking this might be doable in Haskell, is the fact that the few
 combinators I looked at don't recurse down the whole stack.  That, of

I think, it would be possible to define recursion combinators for specific 
patterns, like this functions takes 4 elements from the stack, this one 3 and 
so on, but then you would need combinators for all these patterns, which is 
rather cumbersome.

IMO, it's just not the thing to do things in Haskell exactly like in Joy (or 
in Java, prolog, or - horribile dictu- in C/C++). Even if it's possible, the 
spirit of the languages is so different that you should do the same thing in 
different ways. But of course it's interesting to see whether it can be done.

 course, would be a complete nightmare in Haskell.   Instead they take a
 stack, munge a few (finite number of) items at the top, and return

That's nightmarish enough, because Haskell is strongly typed.
So, if we look at linrec, for example, we find that rec2 and rec1 must return 
the same type as they devour, that's why fact5 doesn't work, because
mult has type 
Num a = (a,(a,b)) - (a,b).

And, BTW, that's why Keean et al's HList library doesn't help here either, the 
type of an HList determines the number of elements and the type of each, so 
there we face the same problems as with nested tuples. What we need is 
type Stack = [ArbitraryType] (from the HList paper, I surmise that [Dynamic] 
would be possilble, but that seems to have it's own problems).

 another stack.  I was hoping that the type variable a in (Integer,
 a) - (Integer, a) would be amorphous enough to match whatever was left
 over after grabbing a few items off the top of this stack.

Well, it's fairly amorphous, but it must be the same type in both 
type-expressions, and that's why the points-free definition of fact doesn't 
type-check without the type signature, the 'fact' in the else-branch is used 
at type (Integer,(Integer,a)) and so on, without the type signature, the 
type-checker assumes that it must be instantiated at exactly the same type, 
which it isn't. With the signature, the type-checker knows that 'fact' is 
polymorphic and that it's perfectly all right to instantiate it at a 
different type in the recursive call. 

Well, at least that's what I worked out from my sparse knowledge, if I'm 
wrong, would somebody please correct me?


 Thanks,

 Greg Buchholz

HTH,
Daniel

Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-07 Thread Keean Schupke
Daniel Fischer wrote:
And, BTW, that's why Keean et al's HList library doesn't help here either, the 
type of an HList determines the number of elements and the type of each, so 
there we face the same problems as with nested tuples. What we need is 
type Stack = [ArbitraryType] (from the HList paper, I surmise that [Dynamic] 
would be possilble, but that seems to have it's own problems).

 

Well it depends on what you want to do... If the types of elements are
determined by the computation then you can use an HList as is, and there
is no problem.
The only time there is a problem is if the _type_ of an element to be put
in an HList depends on an IO action. In this case you need to existentially
quanify the HList.
So you can use the HList in both cases, but you have to deal with 
existential
types if the type of the HList is dependant on IO (you dont have to do this
if only the value of an element depends on IO).

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


Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-07 Thread Greg Buchholz
Daniel Fischer wrote:
 I think, it would be possible to define recursion combinators for specific 
 patterns, like this functions takes 4 elements from the stack, this one 3 and 
 so on, but then you would need combinators for all these patterns, which is 
 rather cumbersome.

Hmm.  The standard Joy combinators probably can't be typed, so maybe
my next step would be to find/create a recursion combinator with a
static type.  Surely one must exist? If you can have a typed lambda
calculus, you must be able to have a typed SK combinator calculus,
right? (Now I'm way out of my league.)  I'll have to think some more on
why you couldn't have a recursion combinator which was more generic than
the one that takes 3 items off the stack, or 4 items, rather than n
items.  Or maybe the whole idea of using a stack is the essential
weakness.

 
 IMO, it's just not the thing to do things in Haskell exactly like in Joy (or 
 in Java, prolog, or - horribile dictu- in C/C++). Even if it's possible, the 
 spirit of the languages is so different that you should do the same thing in 
 different ways. But of course it's interesting to see whether it can be done.

Yeah.  I'm only in it for the brain exercise, not to convert the
masses over to Joy ;-)

  ...another stack.  I was hoping that the type variable a in (Integer,
  a) - (Integer, a) would be amorphous enough to match whatever was left
  over after grabbing a few items off the top of this stack.
 
 Well, it's fairly amorphous, but it must be the same type in both 
 type-expressions, and that's why the points-free definition of fact doesn't 
 type-check without the type signature, the 'fact' in the else-branch is used 
 at type (Integer,(Integer,a)) and so on, without the type signature, the 
 type-checker assumes that it must be instantiated at exactly the same type, 
 which it isn't. With the signature, the type-checker knows that 'fact' is 
 polymorphic and that it's perfectly all right to instantiate it at a 
 different type in the recursive call. 

That pretty much sums up why I thought the whole crazy scheme might
work, only in better words.


Greg Buchholz

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


Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-07 Thread John Meacham
On Mon, Mar 07, 2005 at 08:47:11PM +0100, Daniel Fischer wrote:
 And, BTW, that's why Keean et al's HList library doesn't help here either, 
 the 
 type of an HList determines the number of elements and the type of each, so 
 there we face the same problems as with nested tuples. What we need is 
 type Stack = [ArbitraryType] (from the HList paper, I surmise that [Dynamic] 
 would be possilble, but that seems to have it's own problems).

It would be interesting if you could use the HList framework for
'partially typed lists' in that if your stack is an hlist, an operation
like plus would be
plus :: forall a. HList a = Int :*: Int :*: a - Int :*: a

which says that plus goes from ANY Hlist starting with two ints and
returns that hlist with a single Int on it. basically you use a
universally quantified type to represent the unknown tail of the list
(everything else on the stack).

not sure if it works.. just brainstorming It seems very natural if
it could be made to work.

John



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


Re: [Haskell-cafe] tuples and Show in GHC

2005-03-07 Thread John Meacham
On Mon, Mar 07, 2005 at 03:54:07PM +, Keean Schupke wrote:
 Which almost sounds like a hint to replace the current tuples by
 HLists in Haskell 2? ;)
 
 Something like:
 
 infixr 5 :*:
 data HNil = HNil
 data HList b = a :*: b = a :*: !b deriving (Eq, Ord)
 
 -- type () = HNil
 type (a,b) = a :*: b :*: HNil
 type (a,b,c) = a :*: b :*: c :*: HNil
 
 fst :: HList b = (a :*: b) - a
 fst (a:*:b) = a
 
 Where (x,y,z) is syntactic sugar for x :*: y :*: z :*: HNil in
 much the same way [x,y,z] is syntactic sugar for x:y:z:[]...
 
 It might even be (almost?) backward compatible AFAICS.
 
 Groeten,
 Remi
  
 
 Whilst thats certainly one way to do it, HLists are composed of binary 
 products (,)...  So this
 works as long as you can imagine: (a,(b,(c,HNil))) == (a,b,c)

If we make the list constructor :*: strict in its second argument 
data a :*: b = a :*: !b  
then they are isomorphic, no? 
John

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