4.02 from source: PrelErr interface

1999-02-18 Thread S.D.Mechveliani

Making of  ghc-4.02 (linux-i386)  with  4.01 (linux-i386) 
still fails.
I proceed:

  Create  myfptools/  containing links.
  cd myfptools
  make clean
  ./configure  --prefix=/usr/ghc/4.02
  BTW, where in docs the prefix setting is mentionned?

  create  mk/build.mkwith  GhcHcOpts= -H80m
   BuildingParallel=
   BuildingProfiling=
   BuildingGranSim=
 -H64  was not sufficient!
 And, probably, -O is desirable - ?
 You see, i compile once ghc on a large linux machine and take the 
 binary to my small linux machine of 32M RAM.

  make boot 
says
...
../../glafp-utils/mkdependC/mkdependC -f .depend
   -D__GLASGOW_HASKELL__=402  -- -Iparser -I. -I../includes -O   
--   parser/binding.c
   ...
   parser/syntax.c parser/type2context.c parser/util.c
   parser/infix.c:8: hsparser.tab.h: No such file or directory
 -
...  
the rest of this  boot.log  looks respectable.


  make all  

- it makes new ghc successfully, then
...
rm -f PrelBase.o ; if [ ! -d PrelBase ]; then mkdir PrelBase; 
   else find PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi ;
 ../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing 
  -O -split-objs -odir PrelBase  -H10m  -c
   PrelBase.lhs -o PrelBase.o -osuf o

 PrelBase.lhs:18: Could not find valid interface file `PrelErr'
 PrelBase.lhs:19: Could not find valid interface file `PrelGHC'



Please, advise.

--
Sergey Mechveliani
[EMAIL PROTECTED]






RE: Fixed minor glitches in ghc-4.02

1999-02-18 Thread Simon Marlow

 A typo:
 
 $ diff fptools-orig/ghc/rts/RtsFlags.c fptools/ghc/rts/RtsFlags.c
 219c219
  "  -Msize Sets the maximum heap size (default 64M)  Egs: 
 -M256k -M1G",
 ---
  "  -Msize Sets the maximum heap size (default 64M)  Egs: 
 -H256k -H1G",

Thanks, fixed. 

 Then, ghc refused to compile because of lacking heap. (Although this
 seems a little strange: how did anybody compile it then?)
 
 $ diff fptools-orig/ghc/compiler/Makefile 
 fptools/ghc/compiler/Makefile
 193c193
  rename/ParseIface_HC_OPTS   += -Onot -H75m 
 -fno-warn-incomplete-patterns
 ---
  rename/ParseIface_HC_OPTS   += -Onot -H45m 
 -fno-warn-incomplete-patterns

Firstly, use -dcore-lint when compiling this module (it seems to alleviate a
space leak).  Then ParseIface will compile in about 55M, which is still
very, very bad, but not *as* bad.

The options I use most often to bootstrap the compiler are

GhcHcOpts = -O -dcore-lint -H24m

and possibly -W for fun.

 To increase the heap to 75m, I head to increase the heap limit (-M) as
 well, but the ghc-4.02 from the binary distribution claimed 
 not to know
 about this option. So I browsed through the driver and found the
 following workaround. (Maybe it's clear to you what is going 
 wrong here
 and you know a proper fix? Is it me again?)

Use -optCrts-Msize to pass this option to the compiler proper.
Unfortunately, we've already used -M for something else (to run mkdependHS).
And we really don't anticipate needing to pass -M to the compiler very
often.

Just gotta fix that space leak sigh.

Cheers,
Simon



RE: existential panic in ghc-4.02

1999-02-18 Thread Simon Peyton-Jones

Sergey, thanks for the bug reports

 data R = R {r :: Int}
 rr = R {r=-1}

  ...:4:10: Haskell 98 does not support 'punning' on records 
 on input: "=-"

The error message is unhelpful, but indeed there is a parse error:
'=-' is a valid token in Haskell, different from '=' '-'.

 It reports
   panic! (the `impossible' happened):
 zonkTcTypeToType: free type variable with non-* type: 
 c{-a144-}

Your program is not doing what you expected, and it turned out
to tickle a case whose comment said 'No one in their right mind
will do this, so I won't bother to handle it yet'.  Well you caught
me out.  I've written the code now.

But when you wrote 

data Mix a = Mix [(Key, c a)]

GHC understood this as

data Mix a = Mix (forall c. [(Key, c a)])

which is 99.99% certainly not what you meant.  For existentials you 
have to write

data Mix a = forall c.  Mix [(Key, c a)]

Even then, there is virtually nothing useful you can do with this.
Someone should write a tutorial on what you can do with existential.
Any volunteers?

Simon




RE: Strange ghc-4.02 TC bug?

1999-02-18 Thread Alex Ferguson


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

OK, a typechecker misfeature, then, so I'll cross-reply to ghc-users. ;-)


 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.

That seems a strange thing to do, really.  Isn't the (apparent)
lack of an instance of Eq a, rather than it being sensible to
insist that the superclasses be back-propgated (if I even remotely
understand what's going on here...).


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

Aye, there's the rub.  That's why I think it's a bug, or at least,
a non-optimal resolution of the overlap.  Furthermore, even if
this ought to be rejected, then:  a)  why is it OK if the above
instance declaration appears in a different module;  b)  why is
the overlap error in the reported manner, which is _really_ confusing?
(I had to pretty much use 'divide and conquer' on the source program
to just localise the error, never mind understand it.

Slan,
Alex.



GHC 4.02 patchlevel 1

1999-02-18 Thread Simon Marlow

Ok, 4.02 patchlevel 1 is on the web site, and replaces the original 4.02.

http://research.microsoft.com/users/t-simonm/ghc/

Changes in this release:

- The garbage collector bug is fixed.
- Documentation for scoped type variables included.
- A couple of other minor fixes (empty export lists, etc.)

The source dist and Linux binary dists have been updated, the FreeBSD dist
and a Sparc dist will hopefully follow shortly.

Cheers,
Simon



Announce: Haskell-related Linux RPMs

1999-02-18 Thread Sven Panne

I've uploaded source RPMs and Linux RPMs (glibc) of the following programs
to our FTP server ftp://ftp.informatik.uni-muenchen.de/pub/local/pms :

   * Alex: Chris Dornan's scanner generator for Haskell

   * GHC: The Glorious Glasgow Haskell Compilation System (from CVS)

   * Green Card: A foreign function interface preprocessor for Haskell

   * Happy: An LALR(1) parser generator for Haskell

   * Haskell Direct: An IDL compiler for Haskell

   * Hugs98: A Haskell Interpreter

Examples:

   * Installing Hugs98 on your system:

rpm -i 
ftp://ftp.informatik.uni-muenchen.de/pub/local/pms/hugs98-990121-1.i386.rpm

   * Upgrading to the latest and greatest GHC:

rpm -U ftp://ftp.informatik.uni-muenchen.de/pub/local/pms/ghc-4.03-1.i386.rpm

   * Building Happy locally:

rpm -i ftp://ftp.informatik.uni-muenchen.de/pub/local/pms/happy-1.5-1.src.rpm
rpm -ba --clean /usr/src/packages/SPECS/happy.spec

All binary RPMs install below /usr. IMHO, using a separate hierarchy
like /usr/local is rather pointless with RPM's extensive bookkeeping.

To the ex-Glaswegians: If I read its license correctly, Happy is freely
distributable and GHC's status is changing "real soon now". But what
about Haskell Direct?

Have fun,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



Q: Efficiency of Array Implementation

1999-02-18 Thread Jan Laitenberger


Hi,


I recently noticed in a test program, that updating a table of
fixed size (index and entries of type Int) was slower using an
Array instead of our AVL implementation.

Does anybody know which compiler option I must give on the
command line that the Array is translated to a C array?

I was using ghc-4.01 without special options.


Many thanks in advance,   

Jan

 ___
'---|--
|  __,   _  _  EMail: [EMAIL PROTECTED]
| /  |  / |/ | WWWeb: http://www.uni-passau.de/~laitenbe/
|/\_/|_/  |  |_/
   /| Laitenberger 
--(-|--
   \|




3.02 binary dist for Linux/glibc

1999-02-18 Thread Simon Marlow

Hi Folks,

There's now a 3.02 dist for Linux/glibc available from the web page, or the
Glasgow ftp site:


ftp://ftp.dcs.gla.ac.uk/pub/haskell/glasgow/3.02/ghc-3.02-i386-unknown-linux
glibc.tar.gz

All our future Linux binary bundles are likely to be of the glibc variety,
so if you haven't upgraded your Linux box, now's the time...

On the FreeBSD front, I don't have a FreeBSD 3.xx box available to do builds
on, so if anyone could provide a binary dist for 4.02 I'd be grateful.

4.02 patchlevel 1 will be out momentarily...

Cheers,
Simon



RE: Efficiency of Array Implementation

1999-02-18 Thread Simon Peyton-Jones


 I recently noticed in a test program, that updating a table of
 fixed size (index and entries of type Int) was slower using an
 Array instead of our AVL implementation.
 
 Does anybody know which compiler option I must give on the
 command line that the Array is translated to a C array?
 
 I was using ghc-4.01 without special options.

GHC is very poor on array performance.  To do a halfway good
job we have to get list fusion to work, and that keeps slipping
down the agenda.

Sorry

Simon



Re: how to exploit existentials

1999-02-18 Thread Fergus Henderson

On 17-Feb-1999, S.D.Mechveliani [EMAIL PROTECTED] wrote:
 Who could please, explain a bit existential types?
 
 It is required to organise a table with the key
 
   data K = K1 | K2 | K3  {- ... -}   deriving(Eq,Ord,Enum)
 
 to put/extract there the items of different types, say,  'a'  and 
 ('a','b')  as well.  Is this possible?

Yes.  But what do you want to do with the values once you've extracted them?

 Understanding nothing in this subject, i tried
 
   data KTab = forall a. KT (FiniteMap K a)

That gives you a FiniteMap whose values are all of the same type.
Probably what you really want is something like

data Value = forall v. MkValue v
type KTab = FiniteMap K Value

This gives you single FiniteMap into which you can put values of
different types, so long as you wrap those values using `MkValue'.
You can also extract them from the finite map.  But once you've
extracted them, you can't really do anything useful with them.  If
you want to be able to do something useful with them, e.g. printing
them, then you need to add the appropriate typeclass constraints
to the definition of `Value':

data Value = forall v. show v = MkValue v
   ^

   f :: KTab - KTab 
   f(KT t) = case  addToFM t K1 'a'  of
  t' - KT (addToFM t' K2 ('a','b'))

This would become

   f :: KTab - KTab 
   ft = case  addToFM t K1 (MkValue 'a')  of
  t' - addToFM t' K2 (MkValue ('a','b'))

Here I've added the `MkValue' wrappers and deleted the unnecessary `KT'
wrappers.

 And this does not compile. Then, try
 
   class Tab t k  where  lkp  :: t a - k - Maybe a
 addT :: t a - k - a - t a
 
   instance Tab KTab K  where  lkp (KT t) k = lookupFM t k
 
 Also rejected. How to handle with this?

I'm not sure what you're trying to achieve here.
But maybe you wanted something like this,

class Tab t k v where 
lkp  :: t - k - Maybe v
addT :: t - k - v - t

instance Tab KTab K where
lkp = lookupFM
...

or perhaps this

class Tab t k where 
lkp  :: t - k - Maybe Value
addT :: t - k - Value - t

-- instance definition same as before

?

-- 
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: how to exploit existentials

1999-02-18 Thread Koen Claessen

Jose Emilio Labra Gayo wrote:

 |  data ITEM = forall i . Item i = MkItem i

Don't get me wrong, I think existential types are very useful, but in some
cases the answer is just around the corner in Haskell98, not needing
exisistential types at all.

In this case this could be possible as well.

Suppose your class definition of ITEM looks something like:

  class Item i where
foo :: i - Int
bar :: i - Bool

This means that, after wrapping an object of type i as an ITEM, the only
things you can do with that object are to either apply foo or bar to it.
Why don't we already do that (we are lazy functional programmers, aren't
we?), and define the following type for ITEM:

  data ITEM = MkItem { appliedFoo :: Int, appliedBar :: Bool }

We can introduce a helper function to make things easier:

  mkItem :: Item i = i - ITEM
  mkItem i = MkItem{ appliedFoo = foo i, appliedBar = bar i }

It is clear that this has the same "strength" as the original definition,
but we're not using exisitential types.

Even when the class Item is a little bit more complicated, for example:

  class Item i where
foo  :: i - Int
step :: i - i

We can still use laziness to solve this. What can we do after we have
wrapped a value into an ITEM? We can apply step to it an arbitrary number
of times, and then we can apply foo to that result.

So, we make an infinite list of the possible things we can do:

  data ITEM = MkItem { nStepsThenFoo :: [Int] }

And a helper function:

  mkItem :: Item i = i - ITEM
  mkItem i = MkItem { nStepsThenFoo = map foo (iterate step i) }

Note that, because of laziness, we will actually only compute the result
when we take it out.

I have applied this method several times when I thought I needed
existential types, but I didn't need them at all. I think this might be
the case more often.

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.






Re: Haskell 2 -- Dependent types?

1999-02-18 Thread Josef Sveningsson

On Wed, 17 Feb 1999, George Beshers wrote:

 1.  If the tool can resolve the types (and I would expect this
 to be true most of the time) it can display the types and (if
 the user or style guide dictates) add the types to the source.
 
 2.  If the tool can not resolve the type of a particular
 construct then the programmer can add the information and
 the tool can verify that the supplied type is correct.
 
 3.  As D. Tweed's short STL example points out, C++ can be all
 but unreadable without the support of static analysis tools 
 today (ooh... there was an implicit constructor call there!!!).
 I would argue that working with large software systems in any
 language requires support from software tools. So why not
 design Haskell-2 with tools in mind?
 
For anyone who would like to see what a tool like this *might* look like I
think you should look at Alfa. This tool is really a proof editor but
could as well be used as a programming tool for the functional language
cayenne since the proofs are formulated in cayenne and proof checking is
done by typechecking the program/proof. This can be be done because
cayenne is a language with dependent types which are powerful enough to
express just about anything about the program. The typechecking is done
incrementally which is really neat and prevents you from constructing
erronious proofs/programs. Alfa has a GUI which is really nice and allows
you to just use the mouse for programming/proof construction.

Alfa can be found on:
http://www.cs.chalmers.se/~hallgren/Alfa/

/Josef

--
|Josef Svenningsson|http://www.dtek.chalmers.se/~d95josef|
|Rubingatan 39 |  email: [EMAIL PROTECTED]   |
|421 62 Göteborg   |  tel: 031-7090774   |
--
What is a magician but a practising theorist?
-- Obi-Wan Kenobi






Re: how to exploit existentials

1999-02-18 Thread Koen Claessen

Koen Claessen (me) wrote about transforming away existentials:

 |  I have applied this method several times when I thought I needed
 |  existential types, but I didn't need them at all. I think this might be
 |  the case more often.

Christian Sievers answered:

 | I believe it is always possible, but it soon gets unmanagable.

How about polymorphic member functions in the classes? You will then need
polymorphism in data constructors, which is also an extension of the type
system.

Though, if you only allow existential types that do not refer to member
functions in type classes, then I indeed believe it is always possible.

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.