Re: Strange error in show for datatype

2001-10-05 Thread Bjorn Lisper

Hi again,

My question about my student's problem surely stirred an interesting and
clarifying discussion. Still, I have a question.

Reconsider the example. There's a data type 

data LispList t = Atom t | LispList [LispList t] | Str [Char]

and an instance declaration

instance Show t = Show (LispList t) where
show (Atom t) = show t
show (LispList t) = show t
show (Str t) = show t

So, hypothetically there could have been an additional, overlapping instance
declaration, say

instance Show (LispList Int) where
show (Atom t) = show t
show (LispList t) = show t
show (Str t) = Blahonga!

Then we cannot know whether show (Str HEJ) should yield HEJ or
Blahonga!. However, my student never gave such an overlapping instance,
only the first. So far as I can see there should relly be no ambiguity here!
I'd really like to know what the cause of the problem is.

Björn Lisper

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



Re: Strange error in show for datatype

2001-10-05 Thread Patrik Jansson

On Fri, 5 Oct 2001, Bjorn Lisper wrote:
 My question about my student's problem surely stirred an interesting and
 clarifying discussion. Still, I have a question.
 Reconsider the example.
...
 only the first. So far as I can see there should relly be no ambiguity here!
 I'd really like to know what the cause of the problem is.

The first thing to note is that the compiler will not inspect the code in
your instance, so it has to take the safe route and assume that any
Haskell expression could be used to define show. And as there are examples
which give differenmt results depending on the type, the result will be
considered ambiguous even though your specific show instance would give
the same result for each type.

I just adjusted one the other examples in the thread to your specific case
showing how you can get different results depending on the type.

/Patrik


data LispList t = Atom t | LispList [LispList t] | Str [Char]

instance Show t = Show (LispList t) where
show x = case x of
  Atom t - show t
  LispList t - show t
  Str t  - show (f x)

f :: LispList a - [a]
f _ = []

t = Str hello

test1 = show (t::LispList Int)
test2 = show (t::LispList Char)

main = print (test1, test2, test1==test2)




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



Re: Strange error in show for datatype

2001-10-05 Thread Jan-Willem Maessen

Dylan Thurston [EMAIL PROTECTED] points out my mistake:
  Strictness alas matters.  Here's the witness:
  
  class Num a = ZeroList a where
consZero :: a - [a]
consZero _ = 0:xs
 
 Err, Num a is already a bad context by Simon's criterion because of
 fromInteger, which is what ultimately causes the problem in this
 case.

Quite right.  I overlooked the fact that the superclass constraint
Num a implicitly includes all the methods of Num in ZeroList for
these purposes.

Olaf Chitil [EMAIL PROTECTED] gives an example along the lines I
was attempting (which I've corrected slightly):

 instance Show MyType where
   shows _ = (element of my type ++ )

The important thing here is that the non-strict shows method can make
up any result it likes.

I do think some sort of extended defaulting mechanism as suggested by
Thomas Hallgren would be useful.  Yes, we will occasionally choose
confusing interpretations of e.g.  vs [].  On the other hand, I'm
sure we can warn when defaulting in this way.

But its not the magic bullet against the monomorphism restriction one
might have hoped for...

-Jan-Willem Maessen

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



Re: Strange error in show for datatype

2001-10-04 Thread Dylan Thurston

On Wed, Oct 03, 2001 at 11:52:30AM -0400, Jan-Willem Maessen wrote:
 Earlier, Simon says:
  Indeed, if none of the classes have a method that returns
  an a-value without also consuming one (urk-- strictly, I think, sigh)
  then the same holds.
 
 Strictness alas matters.  Here's the witness:
 
 class Num a = ZeroList a where
   consZero :: a - [a]
   consZero _ = 0:xs

Err, Num a is already a bad context by Simon's criterion because of
fromInteger, which is what ultimately causes the problem in this
case.

I don't see how strictness can be relevant, since it is a property of
a class instance, not a class.

Best,
Dylan

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



Re: Strange error in show for datatype

2001-10-04 Thread Dylan Thurston

On Thu, Oct 04, 2001 at 12:36:55AM -0700, Simon Peyton-Jones wrote:
 So in fact, all we need do is:
   for each class, find the variance of each of its parameters
   in an ambiguous type, zap any positive parameters to Empty
 
 That sounds pretty easy.  We don't need Haskell 2 for that.  I feel
 a little implementation coming on.

This is, nevertheless, an extension to the language, right?  Or is the
class system poorly enough specified that it's unclear?

 Void was a type with one element.  What we really want here is
 a type with no elements.  It's also useful to be able to introduce
 such empty types for phantom-type purposes, so GHC now lets you say
 
   data T
 
 and get a type T with no values.

Ah, excellent!  I've frequently wanted to do this.

Best,
Dylan Thurston

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



Re: Strange error in show for datatype

2001-10-04 Thread Olaf Chitil


 My claim was that
 
 forall a. Show a = T
 
 could be implemented by passing a bottom dictionary for Show.  

Excuse me, but Jan-Willem Maessen has already shown that this
implementation can give unexpected results. A simple example:

instance Show MyType where
  shows _ = (element of my type : )

Then
show (undefined :: MyType)
yields
element of my type

and with the suggested implementation
show undefined
would yield
undefined

The instance may look a bit weird, but in general you cannot assume that
the functions of all instances of all classes are strict. In fact, some
Haskell systems (e.g. nhc98) extend class Show by another method
showsType :: a - String; the function is non-strict in all instances.

Anyway, I find all these suggestions about occurrence and variance of
type variables rather complicated. Worse than the monomorphic
restriction. Admittedly, many Haskell beginners fall into the `show []'
trap. However, this is a chance for the teacher to discuss the problem
(possibly before they fall into the trap). Any type system that prevents
you from making some mistakes has to reject some perfectly sound
programs (because the absence of mistakes is not decidable). Hopefully
the type system is simple enough to enable the programmer to understand
why a program is rejected. And fortunately in this special case there is
a simple way around the problem (specify a type).

By the way, I'm sure some months (a year?) ago there was a similar
discussion about replacing dictionaries by bottom dictionaries on a
Haskell mailing list or comp.lang.functional. Unfortunately I don't find
it anymore.

Ciao,
Olaf

-- 
OLAF CHITIL, 
 Dept. of Computer Science, University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767

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



Re: Strange error in show for datatype

2001-10-04 Thread Koen Claessen

Olaf Chitil wrote:

 | Admittedly, many Haskell beginners fall into the `show
 | []' trap.

Indeed. And this is a perfect example of the fact that all
this bottom-dictionary passing does not work. The type of
the list still matters though:

  Hugs show ([] :: [Char])
  \\

  Hugs show ([] :: [Int])
  []

/Koen


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



Re: Strange error in show for datatype

2001-10-04 Thread Daan Leijen

Koen Cleassen wrote:
 Indeed. And this is a perfect example of the fact that all
 this bottom-dictionary passing does not work. The type of
 the list still matters though:

   Hugs show ([] :: [Char])
   \\

   Hugs show ([] :: [Int])
   []

Koen is absolutely right.  A fundamental property of type-classes
is that you can *not* assign a meaning to the program independent
of its types. A haskell program is not always typeable when I erase
all type signatures because some programs are inherently ambigious,
like showing the empty list. As Koen shows, by giving a type signature
I can disambiguate the program and it indeed gives quite different
results with different type signatures.

A good discussion about this property of type-classes can be found in:

A Second Look at Overloading, Martin Odersky, Philip Wadler, and Martin
Wehr. In Proceedings, ACM Conference on Functional Programming and Computer
Architecture, La Jolla, CA, June 1995.

All the best,
Daan.





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



RE: Strange error in show for datatype

2001-10-04 Thread Simon Peyton-Jones

|  My claim was that
|  
|  forall a. Show a = T
|  
|  could be implemented by passing a bottom dictionary for Show.
| 
| Excuse me, but Jan-Willem Maessen has already shown that this 
| implementation can give unexpected results. 

Yes, I was quite wrong about that.  How embarassing.

But there's still something lurking there.  Consider:

data T a = T1 Int | T2 a

It's clear that (T1 Int) has no a's in it, not even bottom.  Mark
Shields
and ruminated in the corridor about a kind system to make this apparent.
That is, T1 would have type

T1 :: forall a::Pure .  Int - T a

Then if we see (forall a::Pure. Show a = type)
we're justified in fixing a to Empty.   You need a sub-kinding system to
make
this work, so the cost has just gone up.  My implemention mood has
suddenly past.

Isn't laziness wonderful?

Simon


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



Re: Strange error in show for datatype

2001-10-04 Thread Daan Leijen

Simon Peyton-Jones wrote:
 Consider:
 
 data T a = T1 Int | T2 a
 
 It's clear that (T1 Int) has no a's in it, not even bottom.  Mark Shields
 and ruminated in the corridor about a kind system to make this apparent.
 That is, T1 would have type
 
 T1 :: forall a::Pure .  Int - T a
 
 Then if we see (forall a::Pure. Show a = type)
 we're justified in fixing a to Empty.   

I think that even with this kind system, we can't fix it 'a' to Empty. 
For example, the empty list constructor would get type:

[] :: forall (a::Pure) . [a]

and as Koen showed, we still can't fix the 'a' to Empty.

-- Daan.


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



Re: Strange error in show for datatype

2001-10-04 Thread Ross Paterson

On Thu, Oct 04, 2001 at 09:23:10AM +, Marcin 'Qrczak' Kowalczyk wrote:
 Thu, 4 Oct 2001 00:36:55 -0700, Simon Peyton-Jones [EMAIL PROTECTED] pisze:
  Void was a type with one element.  What we really want here is
  a type with no elements.  It's also useful to be able to introduce
  such empty types for phantom-type purposes, so GHC now lets you say
  
  data T
  
  and get a type T with no values.
 
 I think both Void and T have bottom, and both have no other values.

So this extension adds something we already have in Haskell 98, with either

newtype Void = Void Void
or  data Void = Void !Void

(as I think Patrik Jansson pointed out)

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



Re: Strange error in show for datatype

2001-10-04 Thread Marcin 'Qrczak' Kowalczyk

Thu, 4 Oct 2001 14:29:43 +0100, Ross Paterson [EMAIL PROTECTED] pisze:

 So this extension adds something we already have in Haskell 98, with either
 
   newtype Void = Void Void
 ordata Void = Void !Void

Theoretically yes, but this introduces a warning that the data
constructor Void is not used, and it doesn't look clear.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



Re: Strange error in show for datatype

2001-10-04 Thread Marcin 'Qrczak' Kowalczyk

Thu, 4 Oct 2001 06:05:16 -0700, Simon Peyton-Jones [EMAIL PROTECTED] pisze:

   data T a = T1 Int | T2 a
 
 It's clear that (T1 Int) has no a's in it, not even bottom.

instance Show a = Show (T a) where
show x = show (tail [case x of T2 y - y])

We have show (T1 0 :: T Int) == [], show (T1 0 :: T Char) == \\.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



Re: Strange error in show for datatype

2001-10-04 Thread Thomas Hallgren

Olaf Chitil wrote:

Anyway, I find all these suggestions about occurrence and variance of
type variables rather complicated. 

As I suspected, some people are afraid of subtypes :-) But variances are 
not that difficult to compute. For example, it is part of the O'Haskell 
type system, which is implemented in ohugs [1,2].

Koen Claessen wrote:

  Hugs show ([] :: [Char])
  \\

  Hugs show ([] :: [Int])
  []

Oops. I was wrong when I wrote that the proposed way of dealing with 
ambiguity gives the same result as if you manually disambiguate whith an 
arbitrary type. Sorry.

As an example of why passing undefined dictionaries fails, consider how 
'show ([]::[T])' for some type T is computed: it would first call the 
show method of the Show instance for lists, which in turn calls the 
showList method for the type T. Hence, if we pass an undefined 
dictionary for Show a to compute the result of 'show [] :: Show a = 
String', we would try to extract showList from the undefined dictionary, 
leading to an undefined result, rather than a string like []...

But I think the method of simplifying types based on ideas from 
subtyping and using instances for the Empty type (which actually 
contains _|_ , like all other types), could still be useful. It should 
not be seen as a semantics preserving transformation, but as a new kind 
of defaulting mechanism, where default instances are specified by giving 
instance declarations for the Empty type.

For the primary example with the Show class, with this approach, adding

instance Show Empty

would be enough to get

Hugs show []
[]

thanks to the default for the showList method in the Show class. Things like

Hugs show (Left True,Nothing)
(Left True,Nothing)

would also work although the above instance declaration in effect leaves 
the show method for Empty undefined.
 
 (Another way to achieve this would perhaps be to just extend the 
current default declarations to allow defaults to be declared for 
arbitrary classes, not just the Num class...)

Simon-Peyton Jones wrote:

... And you're telling us that the subtyping folk worked this
out yonks ago.  Excellent!  (Reference, for this particular point?)

As I guess has become aparent, I don't have a reference to a complete 
solution to this problem, but using ideas from subtyping to solve this 
has been in the back of my head for many years, although it seems I have 
been too naive, not taking laziness and coherence into account. My 
underlying intuition comes from working with ideas from papers like [3] 
and [4].

My implemention mood has
suddenly past.

Does this mail do anything for your implementation mood?

Thomas Hallgren

PS By the way, perhaps theorems for free (e.g., [5]) also have something 
to contribute to the solution of this problem?

[1] http://www.cs.chalmers.se/~nordland/ohaskell/
[2] http://www.cs.chalmers.se/~nordland/ohugs/
[3] 
http://www.acm.org/pubs/citations/journals/surveys/1985-17-4/p471-cardelli/
[4] http://www.cs.berkeley.edu/~aiken/publications/papers/fpca93.ps
[5] http://www.acm.org/pubs/citations/proceedings/fp/99370/p347-wadler/


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



Re: Strange error in show for datatype

2001-10-03 Thread John Peterson

This problem is probably caused by the unbound type variable in
values like (Str HEJ).

Try giving a specific type as the parameter to LispList:

(Str HEJ :: LispList Int)

The error message here could me more informative!

  John

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



RE: Strange error in show for datatype

2001-10-03 Thread Simon Peyton-Jones

Interesting.  The difficulty (which GHCi has too) is this. Consider

expr = Str foo
msg = show expr

Hugs wants to print msg.  What are the types?

expr :: forall a. LispList a
msg :: forall a.  Show a = String

Urk!  What Show dictionary should Hugs use when evaluating msg?

You may say it doesn't matter, but in general that's not the case.  
In the case of class Num, for example, we might have

expr = 3+4
msg = show expr

and then the type involved really does matter.  In the case of Num
there are defaulting rules, but not for arbitrary user types.

What is particularly annoying here is that it's intuitively obvious that
if we have an expression of type (forall a. LispList a) then it can't
have any useful values of type 'a' in it.  So we can't need to show any
of them.  Hmm.

I wonder if the following is true.  Given the ambiguous type

forall a.  Show a = T  (where a does not appear in T)

it's OK to pass the bottom dictionary.  Furthermore, I claim that 
what makes it OK is that Show has no methods that have 'a' 
in the result that do not also have 'a' in an argument.  The Bad Methods
are like those in Num and Read:

class Num a where
   fromInteger :: Integer - a  -- Bad guy
   ...

class Read a where
  read :: String - a   -- Bad guy
  ...

So (my claim) if none of the classes of the ambiguous type
have a method that returns an a-value, we can definitely 
replace the dictionary with bottom.

Indeed, if none of the classes have a method that returns
an a-value without also consuming one (urk-- strictly, I think, sigh)
then the same holds.

In which case we could report ambiguity a bit less often.  How
useful this would be I don't know.

Simon

| For a change, a teacher asking for help on behalf of a student
| 
| I have a student who wants to emulate S-expressions of Lisp 
| in Haskell. He came up with the following data type:
| 
| data LispList t = Atom t | LispList [LispList t] | Str [Char]
| 
| This works just fine. He then wanted to make it an instance 
| of Show, in order to print values of this type:
| 
| instance Show t = Show (LispList t) where
| show (Atom t) = show t
| show (LispList t) = show t
| show (Str t) = show t
| 
| Now, this compiles and works for some values of the type, but 
| not for all! Here is what happens in hugs:
| 
| hugsprompt  (Atom 1) == 1
| hugsprompt  (LispList [Atom 1, Str HEJ]) == [1,HEJ]  (LispList 
| hugsprompt [Atom 1, LispList [Str HEJ]]) == [1, [HEJ]]  (Str 
| hugsprompt HEJ) == Cannot find show function  
| (LispList [Str 
| hugsprompt HEJ]) == Cannot find show function  
| (LispList [Str 
| hugsprompt HEJ,Atom 1]) == Cannot find show function
| 
| So there is a problem when the value is of form Str string or 
| where such a value is first in the list l in a value of the 
| form LispList l. Oddly enough, such values may appear at 
| other positions without causing any problems.
| 
| I don't think there is a bug in hugs. Similar problems appear 
| if the Show instance is derived, and ghc will also complain - 
| if the definition f = show (LispList [Str HEJ]) is 
| compiled, for instance, the compiler will complain about 
| ambiguous contexts. Ghc will say
| 
| Enrico.hs:1: Ambiguous context `{Show taKi}'
|  `Show taKi' arising from use of `show' at 
| Enrico.hs:17
| 
| and hugs
| 
| Reading file Enrico.hs:
| Type checking  
| ERROR Enrico.hs (line 17): Unresolved top-level overloading
| *** Binding : f
| *** Outstanding context : Show b
| 
| So I wonder whether the infamous Monomorphism Restriction is 
| lurking somewhere here? But I cannot see exactly how right 
| now. Does anyone else have a clue?
| 
| Björn
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

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



RE: Strange error in show for datatype

2001-10-03 Thread Jan-Willem Maessen

Simon Peyton-Jones [EMAIL PROTECTED] tries his hand at
inventing free theorems for qualified types, then concludes:
 In which case we could report ambiguity a bit less often.  How
 useful this would be I don't know.

A lot.  Any time one is testing the empty case of a bulk type.  If
you're coding data structures work (and most first and second year CS
classes will) that happens all the time.  It comes up in situations as
simple as making sure your functions return [] when you expect them
to.

So a clever solution to this problem would make hugs, ghci, etc. far
more usable.  It would also allow the monomorphism restriction to be
relaxed at absolutely no cost in certain cases.

Earlier, Simon says:
 Indeed, if none of the classes have a method that returns
 an a-value without also consuming one (urk-- strictly, I think, sigh)
 then the same holds.

Strictness alas matters.  Here's the witness:

class Num a = ZeroList a where
  consZero :: a - [a]
  consZero _ = 0:xs

instance ZeroList Int

instance ZeroList Double

Now:

(consZero (error no type)) :: (ConsNum a) = [a]
show (consZero (error no type)) :: (ConsNum a) = String

Do we get [0] or [0.0]?

OK, we have a problem worth addressing, and a non-obvious (or absent)
solution.  I'd love to hear what our resident type theorists have to say.

-Jan-Willem Maessen
Eager Haskell Project

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



Re: Strange error in show for datatype

2001-10-03 Thread Thomas Hallgren

  Simon Peyton-Jones wrote:

...
   msg :: forall a.  Show a = String

Urk!  What Show dictionary should Hugs use when evaluating msg?

You may say it doesn't matter, but in general that's not the case.  
In the case of class Num, for example, we might have

   expr = 3+4
   msg = show expr

and then the type involved really does matter.

I wonder if the following is true.  Given the ambiguous type

   forall a.  Show a = T  (where a does not appear in T)

it's OK to pass the bottom dictionary. ...

Type systems with subtyping have what is needed to determine when the 
choice of dictinionary doesn't matter.

In type systems with subtyping, the most general type is the minimal 
type. This means that type variables that occur only positively (in 
covariant positions) can be minimized (and that negative variables can 
be maximized). If there is an empty type, Empty say, which is a subtype 
of all other types, then the type

forall a . Show a = T

is just as general as the type

Show Empty = T

since a occurs only positively in Show a = T, taking into account the 
occurences of a in the definition of the Show class. The requirement 
that a does not appear in T is overly restrictive. This simplification 
can be made as long as all occurences of a in T are positive.

Assuming a language with subtyping that simplifes types in this way, 
expressions like

show undefined
show []
show Nothing
show (Left False)

would no longer be ambiguously overloaded. If the prelude provides

instance Show Empty -- no methods need to be defined

then types of the above expressions would all reduce to String, and they 
would all compute to the expected results (i.e., the result you would 
get by manually disambiguating the types, e.g., show ([]::[Int])).

The same trick applies to the Eq class, so that, e.g., [] == [] would be 
unambiguous and compute to True.

So, obviously, the next version of Haskell should have a type system 
with subtyping, don't you agree? :-) 

Thomas Hallgren

PS In some previous version of Haskell (1.3?), the Prelude defined an 
empty type called Void, but it has since been removed. Apparently, 
people didn't see the potential of Void...

PPS For those who are afraid of subtypes :-), I think you can use the 
information about variance of type variables used in subtype inference, 
to determine when the choice of dictinonary doesn't matter, without 
introducing subtyping in the languange...


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



Re: Strange error in show for datatype

2001-10-03 Thread Carl R. Witty

Bjorn Lisper [EMAIL PROTECTED] writes:

 data LispList t = Atom t | LispList [LispList t] | Str [Char]
 
 instance Show t = Show (LispList t) where
 show (Atom t) = show t
 show (LispList t) = show t
 show (Str t) = show t
 
 hugsprompt  (LispList [Atom 1, Str HEJ]) == [1,HEJ]
 hugsprompt  (LispList [Str HEJ,Atom 1]) == Cannot find show function
 
 So there is a problem when the value is of form Str string or where such a
 value is first in the list l in a value of the form LispList l. Oddly
 enough, such values may appear at other positions without causing any
 problems.

Are you sure about that?  I can't reproduce the above results in hugs
(Hugs 98, February 2000) or ghci (5.02).  I get a much simpler answer:
if the s-expression includes an Atom term, it works; otherwise you get
a type error.  In particular, for the second example above
(LispList [Str HEJ, Atom 1])
both ghci and hugs produce the expected result, rather than failing.

Carl Witty

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