RE: Strange ghc-4.02 TC bug?

1999-02-17 Thread Simon Peyton-Jones

Not a typechecker bug; more a bizarre consequence of 
overlapping instance decls. 

The instance decl 
instance Holidays a = Eq a
overlaps with absolutely every other instance decl for Eq.

In order to make Lattice (Inv a) an instance of Eq, we have
to satisfy Eq (Inv a), since Eq is a superclass of Lattice.
From the data decl, we can get Eq (Inv a) if we can get Eq a.
From the instance decl you commented out, we can get Eq a
if we can get Holidays a.  But then we get stuck.

Admittedly, we can also get Eq a from Lattice a, but GHC's search
doesn't spot that (I'm not quite certain why).

Overlapping instance decls are pretty strong medicine.  use
with care.

Simon

 -Original Message-
 From: Alex Ferguson [mailto:[EMAIL PROTECTED]]
 Sent: Wednesday, February 17, 1999 5:21 PM
 To: [EMAIL PROTECTED]
 Subject: Strange ghc-4.02 TC bug?
 
 
 
 Discern that the following program is apparently well-typed:
 
 
 module M2 where
 
 class Eq a =  Lattice a where
bottom :: a
 
 data Inv a = INV a
  deriving Eq
 
 instance Lattice a = Lattice (Inv a)
 
 
 class Holidays a where
   holCode :: a - Int
 
 -- instance Holidays a = Eq a
 
 
 Now, uncomment the last line, and suddenly:
 
 
 ghc-4.02 -c M2.hs -H30m  -K2M -recomp -fglasgow-exts 
 -cpp -syslib misc 
 -Rgc-stats -dshow-passes -fmax-simplifier-iterations4 
 -funfolding-use-threshold-0 -optC-fallow-undecidable-instances 
 -optC-fallow-overlapping-instances 
 *** Reader:
 *** Renamer:
 *** TypeCheck:
 
 M2.hs:9:
 Warning: No explicit method nor default method for `bottom'
  in an instance declaration for `Lattice'
 
 
 
 M2.hs:9:
 Could not deduce `Holidays a'
 (arising from an instance declaration at M2.hs:9)
 from the context: (Lattice a)
 Probable cause: missing `Holidays a'
 in instance declaration context
 When checking the superclasses of an instance declaration
 
 
 
 
 What gives?  Even more oddly, if this last line is moved to a 
 different
 module, then the problem vanishes.
 
 Slan libh,
 Alex.
 



Strange ghc-4.02 TC bug?

1999-02-17 Thread Alex Ferguson


Discern that the following program is apparently well-typed:


module M2 where

class Eq a =  Lattice a where
   bottom :: a

data Inv a = INV a
 deriving Eq

instance Lattice a = Lattice (Inv a)


class Holidays a where
  holCode :: a - Int

-- instance Holidays a = Eq a


Now, uncomment the last line, and suddenly:


ghc-4.02 -c M2.hs -H30m  -K2M -recomp -fglasgow-exts -cpp -syslib misc 
-Rgc-stats -dshow-passes -fmax-simplifier-iterations4 
-funfolding-use-threshold-0 -optC-fallow-undecidable-instances 
-optC-fallow-overlapping-instances 
*** Reader:
*** Renamer:
*** TypeCheck:

M2.hs:9:
Warning: No explicit method nor default method for `bottom'
 in an instance declaration for `Lattice'



M2.hs:9:
Could not deduce `Holidays a'
(arising from an instance declaration at M2.hs:9)
from the context: (Lattice a)
Probable cause: missing `Holidays a'
in instance declaration context
When checking the superclasses of an instance declaration




What gives?  Even more oddly, if this last line is moved to a different
module, then the problem vanishes.

Slan libh,
Alex.



making 4.02 with 4.01

1999-02-17 Thread S.D.Mechveliani

After applying the *patch* to  .../GC.c  of  ghc-4.02 

i start "making" ghc-4.02 from sources with  ghc-4.01  
- everything - for and under  linux, i386.
So,
  myfptools ...  ./configure;  edit  mk/build.mk;   make all
yields

[...]
gcc -Iparser -I. -I../includes -O-c parser/ctypes.c -o parser/ctypes.o
rm -f libhsp.a
/usr/bin/ar clqs  libhsp.a  parser/binding.o  parser/constr.o  ...
: libhsp.a
gcc -o hsp -Iparser -I. -I../includes -Oparser/printtree.o ...
ghc -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser 
  -iutils:basicTypes:types:hsSyn:...

...

U_binding.hs:148: Could not find valid interface file `FastString'
U_binding.hs:7: Could not find valid interface file `UgenUtil'
U_binding.hs:9: Could not find valid interface file `U_constr'
U_binding.hs:10: Could not find valid interface file `U_list'
U_binding.hs:11: Could not find valid interface file `U_maybe'
U_binding.hs:12: Could not find valid interface file `U_qid'
U_binding.hs:13: Could not find valid interface file `U_ttype'

Compilation had errors



Please, how do i get ghc-4.02 working?


--
Sergey Mechveliani
[EMAIL PROTECTED]






RE: specialization with =

1999-02-17 Thread Simon Peyton-Jones

 SPECIALIZE with '='  is very desirable.
 Otherwise, how can one denote with the same name a function together 
 with its particularly efficient specialization?

Yes it's desirable.  I'm not sure how soon we'll get to it
unless other people start yelling too!  


In general, expect a quiet patch on the GHC develoment front until
March 10th, which is the ICFP submission deadline...

Simon


 Second question: is this hard to implement specializations like
 
   f :: C a = a - ...   -- exported function
   fx = ...
 
   f_spec :: (C a, D a) = a - ...   -- hidden function 
 
   {-# SPECIALIZE f :: (C a,D a) = a - ... = f_spec #-}

Yes, that is harder, because it involves search.  At present
GHC picks the most specific specialisation and never backs out.
Specialisation is currently done well after the type checker,
at which point the compiler doesn't know how to come up with
this new dictionary 'D a'.  This belongs with a bunch of
interesting topics in the 'further extensions of type classes' pile.

 



RE: ghc-4.02 -- space.

1999-02-17 Thread Simon Marlow

 Quite impressed with 4.02 so far -- it walks the walks, see promohype
 elsewhere, why should I give you all too much free advertising? ;-)
 It does indeed seem to be more go-faster than 3.02, _but_:
 
 No profiling!  Boo, hiss.
 
 Funny space behaviour -- a module I have that contains just 
 one king-sized
 constant definition (169K of structured list) now takes 
 _much_ more heap
 to compile with 4.02 vs. 3.02.  Details on request if this is a unduly
 Surprising result.

I've a feeling that the 4.02 compiler is a little more hungry than 3.02, and
we know there's at least one space leak in the 4.xx series.  We'll hopefully
get a chance to take a(nother) look at this before 4.03.

Cheers,
Simon



Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Lennart Augustsson


 I'm not sure that anybody has "accepted"
 undecidable type checking.
People using Gofer or C++ seem to have.

   -- Lennart





Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Lennart Augustsson


 2.in the face of the above, we need to give the compiler more guidance.
 Personally, I favour type declarations everywhere: all identifiers should be
 introduced as being of a particular specified type.
 
 Of course, whether these principles are compatible with Haskell it another
 question...
Giving everything a type certainly is compatible with Haskell.
In Haskell you can almost do it, and the syntax could be
trivially extended to allow it everywhere (i.e. in lambda
and case, and for type variables.)

I think giving types everywhere is an excellent starting point, but
I also feel that it should be relaxed a little, because sometimes it can
be rather redundant.

   -- Lennart





RE: Haskell 2 -- Dependent types?

1999-02-17 Thread D. Tweed

On Wed, 17 Feb 1999, michael abbott wrote:

 As a C++ user (with a background in categories) patiently waiting for
 something a lot better, I personally favour two principles:
 1.let's go for undecidable type checking.  I want the compiler to be able
 to do as much work as possible: ideally, everything that can be resolved at
 compile time should be if only we can express this correctly.
 2.in the face of the above, we need to give the compiler more guidance.
 Personally, I favour type declarations everywhere: all identifiers should be
 introduced as being of a particular specified type.

My personal ideals for a programming language are:

(1) The compiler catches as many language inconsistencies as possible
rather than resolving them in possibly incorrect ways. 

(2) A program should be as easily readible as reasonably possible,
which strongly suggests as free for `noise' as possible.

(For example, try doing simple things with the pair STL class and see how
soon relatively simple expressions become incredibly opaque because of the
sheer length of the identifiers make_pair, .first, .second and the fact
that, to maintain portability to compilers with slightly older versions of
the type-conversion algorithm, you have to write things with casts that
express the desired type

pairfloat,float f=g+make_pair(float(5.0),float(3.0))

and not just

pairfloat,float f=g+make_pair(5.0,3.0)

In practice of course the first problem can be macro'd away.)

Hopefully the above digression supports my case that being explicit
everywhere just to close gaps that can be automatically closed by simple
(and easily human comprehensible) algorithms can make programs much harder
to read, and hence harder to understand and detect algorithmic errors.

I'd prefer only to have to put in type decls for identifiers only when the
compiler genuinely can't use a simple algorithm to deduce the unique
interpretation that fits,PROVIDING THIS ALGORITHM IS SUFFICIENTLY SIMPLE
THAT YOU CAN APPLY IT IN YOUR HEAD. If not then I suppose being explicit
everywhere does become a better way to go.

___cheers,_dave__
email: [EMAIL PROTECTED]   "All shall be well, and all shall be
www.cs.bris.ac.uk/~tweed/pi.htm   well, and all manner of things
work tel: (0117) 954-5253 shall be well." 





Re: A plea for a little Haskell help.

1999-02-17 Thread Fergus Henderson

On 16-Feb-1999, Michael Hobbs [EMAIL PROTECTED] wrote:
 I'm not sure if this can be cleanly done or not. (I've been able to do
 it less-than-cleanly.) What I want to do is define a class where the
 instance has an option of what type of parameters some of its functions
 can accept. For example, say I have
 
 class Foo a where
   write :: a - b - IO ()
 
 This allows a particular instance's version of `write' to accept any
 type of value as the second parameter. However some instances may not be
 able to accept _any_ type of parameter; maybe some can only write
 Strings. I have been able to accomplish what I want by using a bit of a
 kludge:

What's wrong with

class Foo a b where
write :: a - b - IO ()

?

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "Binaries may die
WWW: http://www.cs.mu.oz.au/~fjh  |   but source code lives forever"
PGP: finger [EMAIL PROTECTED]| -- leaked Microsoft memo.






RE: Haskell 2 -- Dependent types?

1999-02-17 Thread michael abbott

As a C++ user (with a background in categories) patiently waiting for
something a lot better, I personally favour two principles:
1.  let's go for undecidable type checking.  I want the compiler to be able
to do as much work as possible: ideally, everything that can be resolved at
compile time should be if only we can express this correctly.
2.  in the face of the above, we need to give the compiler more guidance.
Personally, I favour type declarations everywhere: all identifiers should be
introduced as being of a particular specified type.

Of course, whether these principles are compatible with Haskell it another
question...

-Original Message-
From: Lennart Augustsson [mailto:[EMAIL PROTECTED]]
Sent: 17 February 1999 10:26
To: [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]; [EMAIL PROTECTED];
[EMAIL PROTECTED]
Subject: Re: Haskell 2 -- Dependent types?

 I'm not sure that anybody has "accepted"
 undecidable type checking.
People using Gofer or C++ seem to have.

   -- Lennart






Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Lars Lundgren

On 16 Feb 1999, Carl R. Witty wrote:

 Lars Lundgren [EMAIL PROTECTED] writes:
 
  We have already accepted undecidable type checking, so why not take a
  big step forward, and gain expressive power of a new magnitude, by
  extending the type system to allow dependent types.
 
 Wait a minute...who has accepted undecidable type checking?  Are you
 talking about the new type class features in GHC?  As far as I know,
 those are explicitly documented as experimental, and must be enabled
 by a command-line option.  I'm not sure that anybody has "accepted"
 undecidable type checking.
 

Yes, I was refering to various experimental features in Gofer, and
recently also in GHC. I should not have used the word 'accepted' as I did.
What I meant was that since those features are candidates for haskell 2,
(At least, it is my impression that they are)
we can also consider other extensions wich leads to undecidable type
checking.

Of course, this is not a desirable property, but it may not be that bad in
practice. The type checker can use some default which works in in 95% of
the programs, and the really complex programs can be checked by using a
compiler flag which increases some limit. 

Decidability should not be given up to easily, but i think that dependent
types has a very good price/performance ratio.

/Lars L








Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Fergus Henderson

On 16-Feb-1999, Carl R. Witty [EMAIL PROTECTED] wrote:
 I'm not sure that anybody has "accepted" undecidable type checking.

I think it's becoming clear by now that the theoretical disadvantages
of undecidable type checking are often not significant in practice.
Experience with C++, Gofer, ghc, Mercury, etc. all seems to confirm this.

So if undecidability per se is used as an argument against any particular
proposal for extending the type system, I think that argument should be
considerd a rather a weak one.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "Binaries may die
WWW: http://www.cs.mu.oz.au/~fjh  |   but source code lives forever"
PGP: finger [EMAIL PROTECTED]| -- leaked Microsoft memo.






Re: A plea for a little Haskell help.

1999-02-17 Thread Lennart Augustsson


 What's wrong with
 
   class Foo a b where
   write :: a - b - IO ()
 
 ?
Well, it's not Haskell. :-)

  -- Lennart





XML Haskell (Was: Re: Haskell 2 -- Dependent types?)

1999-02-17 Thread Malcolm Wallace

Alexander Jacobson [EMAIL PROTECTED] writes:

 * facilitate better integration with other languages/systems
 For example, it would be nice to be able either to generate a Haskell
 datatype from an XML DTD or to generate a XML DTD from a Haskell
 datatype.

Funnily enough, that's exactly what we're working on at the moment.  We
already have the part which converts an arbitrary Haskell datatype to
an XML DTD (and values of that type to an XML document).  We are
part-way through the other angle, starting from an arbitrary XML DTD
and deriving a Haskell datatype for it (and the functions which parse
an XML document to a value of that type, and pretty-print the value
back to a document.)  These are written partially using DrIFT (i.e. the
"derive" tool) - which has turned out to be a remarkably pleasant
experience.

We also have a prototype combinator library for manipulating XML
documents in a generic manner (i.e. using a single generic tree
structure for all documents, rather than document-specific types and
values).

If anyone is interested in any of these facilities, drop us an email.

Regards,
[EMAIL PROTECTED]
[EMAIL PROTECTED]







Re: A plea for a little Haskell help.

1999-02-17 Thread Michael Hobbs

Fergus Henderson wrote:
 
 On 17-Feb-1999, Lennart Augustsson [EMAIL PROTECTED] wrote:
 
   What's wrong with
  
   class Foo a b where
   write :: a - b - IO ()
  
   ?
 
  Well, it's not Haskell. :-)
 
 Oh, good point blush.  I forgot about that.
 
 Please take my mail above as a vote in favour of including
 multi-parameter type classes in Haskell-2! ;-)

Actually, that's very close to what I have implemented in Real Life. I'm
not sure of what the semantic meaning of "multi-parameter type classes"
is, but an example of what I actually have defined is something like:

  class Foo a where
write :: a b - b - IO ()

In which case I define instances such as

  data Fooable b = Fooable (IORef b)
  instance Foo Fooable where
write (Fooable ref) val = ...

Anyway, back to the point. I'm not sure if such a concept has yet been
given a name, but it sure would eliminate a lot of headaches if Haskell
provided something like type patterns. Example:

  class Foo a where
write :: a - b - IO ()
  instance Foo TextEntry where
write te (val :: String) = setText te val
write te (val :: Show a = a) = setText te $ show val
write te val = ioError ...

Right now, the only way I can figure out how to do this is to define
something like
  data Show a = WriteVal a b = WVString String | WVShow a | WVElse b
but this is not easily extendable for ad-hoc situations. (I haven't even
verified if the above statement will really work. I have only done the
MaybePoly)

- Michael Hobbs






Re: XML Haskell (Was: Re: Haskell 2 -- Dependent types?)

1999-02-17 Thread Fermin Reig

 
 Alexander Jacobson [EMAIL PROTECTED] writes:
 
  * facilitate better integration with other languages/systems
  For example, it would be nice to be able either to generate a Haskell
  datatype from an XML DTD or to generate a XML DTD from a Haskell
  datatype.
 
 Funnily enough, that's exactly what we're working on at the moment.  We
 already have the part which converts an arbitrary Haskell datatype to
 an XML DTD (and values of that type to an XML document).  We are
 part-way through the other angle, starting from an arbitrary XML DTD
 and deriving a Haskell datatype for it (and the functions which parse
 an XML document to a value of that type, and pretty-print the value
 back to a document.)  These are written partially using DrIFT (i.e. the
 "derive" tool) - which has turned out to be a remarkably pleasant
 experience.

There's another alternative available: asdlGen 

http://www.cs.princeton.edu/zephyr/ASDL/


"ASDL descriptions describe the tree-like data structures such as
abstract syntax trees (ASTs) and compiler intermediate representations
(IRs). Tools such as asdlGen automatically produce the equivalent data
structure definitions for C, C++, Java, Standard ML, and
Haskell. asdlGen also produces functions for each language that read
and write the data structures to and from a platform and language
independent sequence of bytes. The sequence of bytes is called a
pickle. "

I think there's also some support for XML.

I'm not sure if asdlGen can do all that Malcolm and Colin's package
will do, though. In any case, I find the ability to write a pickle
from C and read back from Haskell quite useful. 

Two relevant papers are:

"Early Experience with ASDL in lcc", Software-Practice and Experience,
to appear.

"A Machine-Independent Debugger-Revisited", Microsoft Research TR 99-4

both available at http://www.research.microsoft.com/~drh/

 If anyone is interested in any of these facilities, drop us an email.

Do keep the mailing list informed of your progress!



Regards,

Fermin Reig