RE: ANNOUNCE: GHC version 5.04 released

2002-07-22 Thread Simon Marlow


 I've patched up an install script for OpenBSD users of GHC who:
 
 -  would like to install it somewhere other than /usr/local
 -  do not have root priviledges on their machine
 
 Note that uninstallation must be by hand if you use this script, as we
 bypass the pkg system.

Could this be done using GHC's normal binary distribution mechanism?  In
a build tree you do the following:

  - add the line 'BIN_DIST=1' to mk/build.mk
  - build everything (inc. profiling libraries if required)
  - say 'make binary-dist Project=Ghc' at the top level
  - tar up the contents of ghc-5.04 and ship it

this gives you a tarball which can be unpacked and used in-place or
installed elsewhere in the filesystem.

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



RE: Type of newForeignPtr addForeignPtrFinalizer

2002-07-22 Thread Simon Marlow

[ sorry for the delay in replying to this one, I'm just trying to
clear some of my backlog... ]

 I have a feeling this may be a stupid question, but why are the
 types of these..
  newForeignPtr  :: Ptr a - IO () - IO (ForeignPtr a)
  addForeignPtrFinalizer :: ForeignPtr a - IO () - IO ()
 (second arg being the finalizer)
 
 Won't a finaliser almost always take a pointer to the thing being
 finalised as an argument? If so it would be more convienient
 to have newForeignPtr..
  newForeignPtr :: Ptr a - (Ptr a - IO ()) - IO (ForeignPtr a)
 or maybe..
  newForeignPtr :: Ptr a - (ForeignPtr a - IO ()) - IO 
 (ForeignPtr a)

I think the reason was simplicity - I seem to recall we originally had
the versions you suggested, but realised that it isn't *necessary* for
the finalizer to take a Ptr as an argument.

Anyway, there's an ongoing discussion on the FFI list about whether
having arbitrary Haskell finalizers is really a plausible design, so it
may be that the point is moot anyway.

 The first of these is easy to implement yourself I suppose..
  myNewForeignPtr :: Ptr a - (Ptr a - IO ()) - IO (ForeignPtr a)
  myNewForeignPtr p fin = newForeignPtr p (fin p)
 
 The second seems to require this bit of weirdness..
  myNewForeignPtr :: Ptr a - (ForeignPtr a - IO ()) - IO 
 (ForeignPtr a)
  myNewForeignPtr p fin = do
newfp  - newForeignPtr p (return ())
addForeignPtrFinalizer newfp (fin newfp)
return newfp

You can do this more easily using fixIO:

   myNewForeignPtr p fin = do
fixIO (\fp - newForeignPtr p (fin fp))

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



RE: fno-implicit-prelude and literal numeric patterns

2002-07-22 Thread Simon Peyton-Jones


| The user's guide is silent about which version of Eq is used 
| for literal patterns, but I assume that it follows the (n+k) 
| example and so Prelude Eq is used for the overloaded use of ==.

That's right.  I'll add a note to that effect in the users guide.

| What is the reason for using Prelude.Ord (and Prelude.Eq)? 
| 
| This seems very limiting since you can replace Num but you 
| can't replace Eq, and moreover, your new versions of the 
| Numeric classes must be subclasses of Prelude.Eq, rather than 
| another Eq. 
|...
| Is there are strong reason for avoiding the alternative: 
| whatever == and = are in scope? Perhaps it is the 
| if-then-else that must refer to Prelude.Bool?

Well, I had to stop somewhere.  (As I have previously remarked on this
thread, it is hard to make *everything* rebindable.)  With more effort
one could make more things rebindable.

My goal was to make numerics completely rebindable; the current
omission is (only) the handling of defaults.  

At the moment I simpy don't know what a good 'final' design might be,
and I'm pretty reluctant to develop this feature incrementally.  If a 
consensus emerges,  then yes (unless it's a heart-and-lung job) I'll
implement it or help one of you to do so.

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



RE: make -j2 fails on SMP with ghc-5.04

2002-07-22 Thread Simon Marlow

 On Monday 15. July 2002 12:38, Simon Marlow wrote:
   I have a dual Athlon box, make -j2 fails, but make works.
   Is that normal?
 
  I did some tweaking to the build system to help -jN builds, but I
  haven't tested a complete build this way.  Whereabouts does 
 it fall over
  for you?
 
 I also experienced such a strange failure with -j2 on my 
 uniprocessor Athlon.
 The problem was the glafp-utils/mkdependC/mkdependC script 
 that is generated 
 during the build. The build gave a seemingly senseless error 
 message so I 
 looked at the script. Appearently, to concurrent make 
 processes had tried to 
 assemble it simultaneously, generating a pretty twisted version.

Which version was this?  The fixes for 'make -j' went in after 5.02.
I've tried 'make -j2' in glafp-utils and it appears to work fine.

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



FreeBSD port for 5.04 now committed

2002-07-22 Thread Simon Marlow

The FreeBSD folks have been kind enough to commit the update for the ghc
port to 5.04.  FreeBSD users: cvsup your /usr/ports, cd
/usr/ports/lang/ghc  make install, or wait for the package to appear
on your local mirror site and try 'pkg_add -r ghc'.

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



Deadlock detection different in ghc-5.04?

2002-07-22 Thread Volker Stolz

Hi, for some concurrency abstractions I decided to use deadlock
detection by means of exceptions which didn't work out as expected.
Below is some simplifed source code showing the problem: My assumption
was since GHC should be able to detect that the child still has a
reference to mv_should_work -- although in an exception handler -- the
RTS would never decide to kill the other thread.

Unluckily, this assumption turned out to be false. Did I overestimate
GHC's capabilities or is this a bug? Especially as ghc-5.02.2 shows the
desired behaviour (you just need to drop the Control.)...
Instead of exiting silently, the program terminates in the exception handler
in the main thread with ghc-5.04.

\begin{code}
module Main where

import Concurrent
import qualified Control.Exception

main = do
  mv_should_work - newEmptyMVar
  mv_deadlock - newEmptyMVar
  forkIO $ do
Control.Exception.catch (takeMVar mv_deadlock) -- deadlock
(\ e - putMVar mv_should_work ())
  yield  yield   yield
  Control.Exception.catch (takeMVar mv_should_work)
  (\ e - putStrLn $ main caught:  ++ (show e))
\end{code}
-- 
Volker Stolz * http://www-i2.informatik.rwth-aachen.de/stolz/ * PGP * S/MIME
http://news.bbc.co.uk: `Israeli forces [...], declaring curfews that
confine more than 700,000 people to their homes.'
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: comparison of execution speed of array types

2002-07-22 Thread Hal Daume III

 Could you try IOUArray for completeness too?  (An IOUArray is the
 unboxed version of IOArray, it can be found in Data.Array.IO).

It fits in as the fastest:

IOUnboxedMutArray 0.48u 0.04s 0:00.58 89.6%

  NormalArray   1.65u 0.20s 0:01.89 97.8%
  NormalArrayReplace2.40u 0.08s 0:02.56 96.8%
  UnboxedArray  0.80u 0.04s 0:00.87 96.5%
  UnboxedArrayReplace   1.83u 0.07s 0:01.99 95.4%
  IOMutArray0.60u 0.03s 0:01.09 57.7%

 You could try testing DiffArray (Data.Array.Diff) which is optimised for
 in-place updates, and should show a bigger difference between the normal
 and 'replace' versions.  It might be nearly as fast as IOArray (I don't
 think we've ever benchmarked it), and it doesn't need to be in the IO
 monad.

DiffArray seems to be broken :).  Either that or I'm using it
incorrectly.  I've attached the relevant code, but when I don't reverse
the array everything works fine; when I reverse it the program doesn't
(seem to) halt.

module Main
where

import Data.Array.IO
import Data.Array.Diff

testArray :: IOToDiffArray IOArray Int Int
testArray = array (0,5) [(i, (19*i+23) `mod` 911) | i - [0..5]]

reverseArray :: IOToDiffArray IOArray Int Int - IOToDiffArray IOArray Int
Int
reverseArray arr = 
arr // [(5-i, arr!i) | i - [0..5]]

sumArrayMod :: IOToDiffArray IOArray Int Int - Int
sumArrayMod arr = sumArrayMod' low 0
where sumArrayMod' pos sum 
 | pos  high = sum
 | otherwise  = sumArrayMod' (pos+1) ((sum +
arr!pos) `mod` 911)
  (low,high) = bounds arr

main = print $ sumArrayMod $reverseArray testArray




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



RE: Deadlock detection different in ghc-5.04?

2002-07-22 Thread Simon Marlow

 Hi, for some concurrency abstractions I decided to use deadlock
 detection by means of exceptions which didn't work out as expected.
 Below is some simplifed source code showing the problem: My assumption
 was since GHC should be able to detect that the child still has a
 reference to mv_should_work -- although in an exception handler -- the
 RTS would never decide to kill the other thread.
 
 Unluckily, this assumption turned out to be false. Did I overestimate
 GHC's capabilities or is this a bug?

It's not a bug, but it's quite tricky to explain.

The effect you're seeing is this: GHC 5.04 is a bit more general in
dealing with deadlocks, in that it doesn't automatically assume that the
main thread is alive (GHC 5.02 did make that assumption).  In your
example, at the point of the deadlock *both* threads are blocked on
unreachable MVars, so both threads get an exception.  The RTS has no way
to know that if it woke up the child thread first, then this would also
unblock the main thread.

I've cut-n-pasted the trace below (you can get this by compiling the RTS
with -DDEBUG and running the program with +RTS -D1; arguably this is so
useful that we ought to take it out from under -DDEBUG).

Cheers,
Simon

DEBUG (-D1): scheduler
scheduler: created thread 1, stack size = f4 words
scheduler: == scheduler: waiting for thread (1)

scheduler: == scheduler: waiting for thread (1)

scheduler: == scheduler: new main thread (1)

scheduler: all threads:
thread 1 @ 0x500c is not blocked
scheduler: -- Running TSO 1 (0x500c) ThreadEnterGHC ...
scheduler: created thread 2, stack size = f4 words
scheduler: -- thread 1 (0x500c; ThreadRunGHC) stopped, yielding
scheduler: all threads:
thread 2 @ 0x500c0400 is not blocked
thread 1 @ 0x500c is not blocked
scheduler: -- Running TSO 2 (0x500c0400) ThreadEnterGHC ...
scheduler: -- thread 2 (0x500c0400) stopped: is blocked on an MVar
scheduler: all threads:
thread 2 @ 0x500c0400 is blocked on an MVar
thread 1 @ 0x500c is not blocked
scheduler: -- Running TSO 1 (0x500c) ThreadRunGHC ...
scheduler: -- thread 1 (0x500c; ThreadRunGHC) stopped, yielding
scheduler: all threads:
thread 2 @ 0x500c0400 is blocked on an MVar
thread 1 @ 0x500c is not blocked
scheduler: -- Running TSO 1 (0x500c) ThreadRunGHC ...
scheduler: -- thread 1 (0x500c; ThreadRunGHC) stopped, yielding
scheduler: all threads:
thread 2 @ 0x500c0400 is blocked on an MVar
thread 1 @ 0x500c is not blocked
scheduler: -- Running TSO 1 (0x500c) ThreadRunGHC ...
scheduler: -- thread 1 (0x500c) stopped: is blocked on an MVar
scheduler: all threads:
thread 2 @ 0x500c0400 is blocked on an MVar
thread 1 @ 0x500c is blocked on an MVar
scheduler: deadlocked, forcing major GC...
scheduler: resurrecting thread 1
scheduler: raising exception in thread 1.
scheduler: raising exception in thread 1.
scheduler: resurrecting thread 2
scheduler: raising exception in thread 2.
scheduler: raising exception in thread 2.
scheduler: -- Running TSO 2 (0x500bf000) ThreadEnterGHC ...
scheduler: --++ thread 2 (0x500bf000) finished
scheduler: all threads:
thread 2 @ 0x500bf000 has completed
thread 1 @ 0x500bf400 is not blocked
scheduler: -- Running TSO 1 (0x500bf400) ThreadEnterGHC ...
main caught: thread blocked indefinitely
scheduler: --++ thread 1 (0x500bf400) finished
scheduler: all threads:
thread 2 @ 0x500bf000 has completed
thread 1 @ 0x500bf400 has completed
== scheduler: main thread (1) finished
scheduler: created thread 3, stack size = f4 words
scheduler: == scheduler: waiting for thread (3)

scheduler: == scheduler: waiting for thread (3)

scheduler: == scheduler: new main thread (3)

scheduler: all threads:
thread 3 @ 0x500bd028 is not blocked
thread 2 @ 0x500bf000 has completed
thread 1 @ 0x500bf400 has completed
scheduler: -- Running TSO 3 (0x500bd028) ThreadEnterGHC ...
scheduler: --++ thread 3 (0x500bd028) finished
scheduler: all threads:
thread 3 @ 0x500bd028 has completed
thread 2 @ 0x500bf000 has completed
thread 1 @ 0x500bf400 has completed
== scheduler: main thread (3) finished
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



error building greencard with ghc 5.04

2002-07-22 Thread Hal Daume III

probably a result of the libraries (probably = certainly), but i get:

../../src/green-card --target ghc StdDIS.gc
ghc -fglasgow-exts -fno-prune-tydecls -fvia-C -package lang -package util
-c StdDIS.hs -o StdDIS.o

StdDIS.hs:39: Module `Foreign' does not export `ForeignObj'

StdDIS.hs:39: Module `Foreign' does not export `makeStablePtr'

StdDIS.hs:39:
Module `Foreign' does not export `addForeignFinalizer'

StdDIS.hs:39: Module `Foreign' does not export `makeForeignObj'
gmake[2]: *** [StdDIS.o] Error 1


anyone have a patch?

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

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



Re: error building greencard with ghc 5.04

2002-07-22 Thread Alastair Reid


 anyone have a patch?

I think the CVS repository has a patch.

If not, try adding 'import ForeignObj' to StdDIS.gc.
Probably wise to reexport ForeignObj from StdDIS.gc too.
[Can't test this since I'm using someone else's box this week and
it'll take a few days for my upgrade to 5.04 request to go through.]

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: comparison of execution speed of array types

2002-07-22 Thread Manuel M T Chakravarty

Hal Daume III [EMAIL PROTECTED] wrote,

 clearly IOMutArray is the best, even outperforming the
 UnboxedArray.  Unfortunately, writing code in the IOMutArray format is
 much uglier than writing it in the UnboxedArray or NormalArray formats,
 even though I know that I'm never going to refer to an old version of the
 array, so inplace updates are a-okay.
 
 So my question is: how can I get better performance without wrapping
 everything in the IO (or some other) monad?

Shameless Plug
  This question is the motivation for our work on optimising
  array codes: http://www.cse.unsw.edu.au/~chak/papers/CK01.html
  Unfortunately, I can't point you to a web site where you
  can download everything ready to run, but the plan is to
  have some library code for more general consumption ready
  in the next couple of weeks.
/Shameless Plug

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