GHC 5.02.3, SuSE rpms

2002-04-09 Thread Ralf Hinze

I've uploaded SuSE 7.3 rpms for the patchlevel release of the Glasgow
Haskell Compiler (GHC), version 5.02.3.

http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.src.rpm
http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.i386.rpm
http://www.informatik.uni-bonn.de/~ralf/ghc-prof-5.02.3-1.i386.rpm

Enjoy, Ralf
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: GHC 5.02.3, SuSE rpms

2002-04-09 Thread Simon Marlow


 I've uploaded SuSE 7.3 rpms for the patchlevel release of the Glasgow
 Haskell Compiler (GHC), version 5.02.3.

Thanks; slurped  added to the download page.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: An answer and a question to GHC implementors [was Re: How to make Claessen's Refs Ord-able?]

2002-04-09 Thread Simon Marlow


  However, it is possible to have global top-level references using
  unsafePerformIO if you're very careful about it.  In GHC we 
 do something
  like this:
  
  {-# NOINLINE global_var #-}
  global_var :: IORef Int
  global_var = unsafePerformIO (newIORef 42)
  
  the NOINLINE pragma is used to ensure that there is 
 precisely *one* copy
  of the right hand side of global_var in the resulting 
 program (NOTE: you
  also need to compile the program with -fno-cse to ensure that the
  compiler doesn't also common up the RHS of global_var with 
 other similar
  top-level definitions).
 
 this usage of unsafePerformIO is such a staple of real-world Haskell
 programming, it seems there should be some language (or experemental
 compiler *wink wink ghc nudge*) support for it. I am not sure 
 what form
 it would take though.

muse
I did wonder once whether IO monad bindings should be allowed at the
top-level of a module, so you could say

 module M where
 ref - newIORef 42

and the top-level IO would be executed as part of the module
initialization code.  This solves the problems with unsafePerformIO in a
cleanish way, but would add some extra complexity to implementations.
And I'm not sure what happens if one top-level IO action refers to other
top-level IO bindings (modules can be recursive, so you could get loops
too).
/muse

 getGlobalVar :: IO (IORef Int)
 getGlobalVar = memoIO (newIORef 42) 
 
 note that this is not exactly the same since getting the global var is
 in the io monad, but that really makes sense if you think 
 about it. and
 chances are you are already in IO if you need an IORef.

This doesn't really solve the problem we were trying to solve, namely
that passing around the IORef everywhere is annoying.  If we were happy
to pass it around all the time, then we would just say

   main = do 
  ref - newIORef 42
  ... pass ref around for ever ...

We could use implicit parameters, but that means changing the types of
lots of functions, and that's just as annoying as actually passing the
arguments around explicitly.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: GHCi and -O [was: Re: ANNOUNCE: GHC 5.02.3 released]

2002-04-09 Thread Simon Marlow


 This made me think about using *.o-files in GHCi generated w/ 'ghc
 -O2'. My GHCi (currently 5.00.2) states:
 
 --- snip ---
 warning: -O conflicts with --interactive; -O turned off.
 --- snap ---
 
 if I pass -O2 to ghci.
 
 Additionally, I recall some core-dumps or having ghci sometimes report
 missing symbols if using some modules compiled w/ optimization.
 
 So, is GHCi supposed to work w/ optimized modules after all?

Sure, GHCi is supposed to be able to load optimised object code just as
well as non-optimised object code.  If it doesn't, this is a bug.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: An answer and a question to GHC implementors [was Re: How to make Claessen's Refs Ord-able?]

2002-04-09 Thread David Feuer

On Tue, Apr 09, 2002, Simon Marlow wrote:
 muse
 I did wonder once whether IO monad bindings should be allowed at the
 top-level of a module, so you could say
 
  module M where
  ref - newIORef 42
 
 and the top-level IO would be executed as part of the module
 initialization code.  This solves the problems with unsafePerformIO in a
 cleanish way, but would add some extra complexity to implementations.
 And I'm not sure what happens if one top-level IO action refers to other
 top-level IO bindings (modules can be recursive, so you could get loops
 too).
 /muse

First-class modules could (I believe) solve this problem quite neatly.

David
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ghc 5.02.2 FFI question

2002-04-09 Thread Bernard James POPE

Hi Simon,

(posted to [EMAIL PROTECTED] in case anyone else is
reading this).

 I just tried your example and it seems to run in constant space here
 with 5.02.2.  The code looks fine - this isn't something we really
 envisaged people doing with the RTS API, but there's no real problem
 with it except that of course you don't get the benefits of type
 checking.  I'm sure you have very good reasons for building Haskell
 expressions in C :-)

My motivation is debugging. I was trying to implement a similar interface
to the HugsInternals one. I succeeded except the I noticed what looked to
me like a space leak, so I simplified the program a bit.

 Can you give us any more clues?  What were the symptoms when you ran it?

Okay, I've simplified the program even more. Now I just have a program that
calls a C function to build a Double, and then passes a stable pointer
back to it.

For comparison, I also made it possible to avoid calling C, ie just build
a Double in Haskell and make a stable pointer reference to it in Haskell.

My intuition, which maybe very wrong, is that the two ways of executing
should have very similar memory profiles and time performance. They run
in about the same time. Both processes grow bigger over time (as you will
see below), but the one that calls C grows much much faster. I'm presuming
that I can rely on the unix program 'top' to give me reasonably good
results.

First the code, then the profiles:

The Haskell code.



   module Main where

   import Foreign

   -- returns a stable pointer to a Double (489.0923)
   foreign import leak leak :: IO (StablePtr Double)

   -- change to callLeak' to compare behaviour
   main = do repeatIO 50 callLeak

   -- call into C to make a Double
   callLeak :: IO ()
   callLeak = do doubleSPtr - leak
 doubleVal  - deRefStablePtr doubleSPtr
 freeStablePtr doubleSPtr
 print doubleVal


   -- don't call into C
   callLeak' :: IO ()
   callLeak' = do doubleSPtr - newStablePtr (489.0923::Double)
  doubleVal  - deRefStablePtr doubleSPtr
  freeStablePtr doubleSPtr
  print doubleVal



The C code:



   #include /home/bjpop/ghc-5.02.2/ghc/includes/Rts.h
   #include /home/bjpop/ghc-5.02.2/ghc/includes/RtsAPI.h
   #include LeakC.h

   StgStablePtr leak (void)
   {
   StgClosure *num;
   num = rts_mkDouble(489.0923);
   return (getStablePtr ((StgPtr)(num)));
   }



Okay, now for the tests:

If I compile the program so that it calls to C via the FFI 
then this is what top gives me over 30 second samples:

SIZE RSS  TIME
--
1708 1708 0:00
2748 2748 0:30
3772 3772 1:00
4788 4788 1:30
5828 5828 2:00
6812 6812 2:30

The process is definitely growing in size, and it looks linear.



If I compile the program so that it does not call C
(by modifying the definition of main so that it uses callLeak')
then this is what top gives over 30 second samples:

SIZE RSS  TIME
--
1692 1692 0:00
1704 1704 0:30
1720 1720 1:00
1736 1736 1:30
1752 1752 2:00
1764 1764 2:30

The process is still growing, but very slowly. I wouldn't expect
it to grow at all, but I don't know the memory management of
ghc well enough to be sure.



I thought I should look at the output from the garbage collector to see
if anything obvious came up. The verbose mode of '+RTS -S -RTS' spat out
lots of stuff as you would guess. I can post a snippet to you if it is of
interest, but I'll wait to see what you say.

The not-verbose output is as follows:



When calling C:

   2,460,833,948 bytes allocated in the heap
 1,911,280 bytes copied during GC
26,192 bytes maximum residency (1 sample(s))
   
  7500 collections in generation 0 (  1.79s)
 1 collections in generation 1 (  0.00s)
   
 1 Mb total memory in use
   
 INIT  time0.01s  (  0.00s elapsed)
 MUT   time  160.84s  (410.71s elapsed)
 GCtime1.79s  (  3.94s elapsed)
 EXIT  time0.00s  (  0.00s elapsed)
 Total time  162.64s  (414.65s elapsed)
   
 %GC time   1.1%  (1.0% elapsed)
   
 Alloc rate15,298,936 bytes per MUT second
   
 Productivity  98.9% of total user, 38.8% of total elapsed



When not calling C:

   2,454,983,980 bytes allocated in the heap
 1,911,300 bytes copied 

Re: GHC 5.02.3, SuSE rpms

2002-04-09 Thread Jorge Adriano

On Tuesday 09 April 2002 08:38, Ralf Hinze wrote:
 I've uploaded SuSE 7.3 rpms for the patchlevel release of the Glasgow
 Haskell Compiler (GHC), version 5.02.3.

   http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.src.rpm
   http://www.informatik.uni-bonn.de/~ralf/ghc-5.02.3-1.i386.rpm
   http://www.informatik.uni-bonn.de/~ralf/ghc-prof-5.02.3-1.i386.rpm

 Enjoy, Ralf

Thanks for maintaning the Ghc SuSE Rpms :)
Is there any chance to make this available in SuSEs ftp server?
I ask this becouse it would be nice to have ghc ugrades listed in YOU (Yast 
Online Update) and apt (there is already apt for SuSE, I'm using it and it is 
great). This way every SuSE users of ghc would be able to keep their ghc 
version up to date easily even if they're not on haskell mailing lists. 

Thanks,
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ANNOUNCE: GHC 5.02.3 released

2002-04-09 Thread Manuel M. T. Chakravarty

Simon Marlow [EMAIL PROTECTED] wrote,

The (Interactive) Glasgow Haskell Compiler -- version 5.02.3
   ==
 
 We are pleased to announce a new patchlevel release of the Glasgow
 Haskell Compiler (GHC), version 5.02.3.  The source distribution is
 freely available via the World-Wide Web, under a BSD-style license.
 See below for download details.  Pre-built packages for Linux,
 FreeBSD, Solaris and Win32 are also available (or will appear
 shortly).

There are now binary RPM packages for x86/Linux built with
RedHat 7.2 (against glibc 2.2):

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-5.02.3-1.i386.rpm
  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-prof-5.02.3-1.i386.rpm
  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-doc-5.02.3-1.i386.rpm

The ghc-prof package contains optional libraries for
profiling and the ghc-doc package contains optional
documentation.  The preformatted documentation is also
available online from the GHC Web page.

The matching source RPM is at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/ghc-5.02.3-1.src.rpm

Cheers,
Manuel
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: Fundep/Existential Types in 5.03

2002-04-09 Thread Ashley Yakeley

At 2002-04-09 20:02, I wrote:

Does anyone even know of a workaround? Given this, find an implementation 
of 'f' that retrieves the contents of its 'D' argument:

  class C a b | a - b

  data D a = forall b. (C a b) = MkD b

  f :: (C a b) = D a - b
  -- f (MkD b) = bwon't compile

It's very annoying if it can't be done.

Oh, I suppose I can always do this:

  data D a b = MkD b

...so perhaps in all fairness it's not quite so annoying.


-- 
Ashley Yakeley, Seattle WA

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users