Foreign.StablePtr: nullPtr double-free questions

2013-03-08 Thread Remi Turk
Good night everyone,

I have two questions with regards to some details of the
Foreign.StablePtr module. [1]

1) The documentation suggests, but does not explicitly state, that
  castStablePtrToPtr `liftM` newStablePtr x
will never yield a nullPtr. Is this guaranteed to be the case or not?
It would conveniently allow me to store a Maybe for free, using
nullPtr for Nothing, but I am hesitant about relying on something that
isn't actually guaranteed by the documentation.

2) If I read the documentation correctly, when using StablePtr it is
actually quite difficult to avoid undefined behaviour, at least in
GHC(i). In particular, a double-free on a StablePtr yields undefined
behaviour. However, when called twice on the same value, newStablePtr
yields the same StablePtr in GHC(i).
E.g.:

module Main where

import Foreign

foo x y = do
p1 - newStablePtr x
p2 - newStablePtr y
print $ castStablePtrToPtr p1 == castStablePtrToPtr p2
freeStablePtr p1
freeStablePtr p2 -- potential double free!

main = let x = Hello, world! in foo x x -- undefined behaviour!

prints True under GHC(i), False from Hugs. Considering that foo
and main might be in different packages written by different authors,
this makes correct use rather complicated. Is this behaviour (and the
consequential undefinedness) intentional?

With kind regards,

Remi Turk

[1] 
http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.6.0.1/Foreign-StablePtr.html

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-14 Thread Remi Turk
On Thu, Feb 12, 2009 at 08:47:36AM +, Simon Marlow wrote:
 Remi Turk wrote:
 On Tue, Feb 10, 2009 at 01:31:24PM +, Simon Marlow wrote:
 My vote would be:

 :info class Show
 :info type Show
 :info instance Show

 where

 :info Show

 displays information about everything called Show

 I know that classes and types share the same namespace currently, but 
 it  might not always be so.

 Sounds good in principle, and has the advantage of being 100%
 backward compatible, but :i class Show for the common case
 (ahum, _my_ common case at least ;) still seems rather verbose,
 so how to abbreviate that?

 How about a macro?

 :def ic return . (:info class  ++)

Ah of course, I keep forgetting about :def :)

Note that when classes and types would stop sharing their namespace,
:info instance Show would again be ambiguous though..

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-11 Thread Remi Turk
On Tue, Feb 10, 2009 at 01:31:24PM +, Simon Marlow wrote:
 Remi Turk wrote:
 On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
 On 2009 Feb 5, at 5:49, Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set 
 of  commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show
 (...)
 However, it would make :i ambiguous, which is rather sad.
 :class Show -- unique prefix :cl, already many such collisions
 :instance Show

 That could work, but then how to get information about types as
 opposed to classes? Its not in the above example, but Show
 actually stands for an arbitrary typeclass _or type_.

 However, as igloo pointed out on the ticket, abbreviations don't
 actually have to be unique:

  For example, :b means :break even though we also have :back, :browse and 
 :browse!.  [1]

 That would personally lead me to prefer the :info/:instances
 combo, with :i as an abbreviation of :info.

 My vote would be:

 :info class Show
 :info type Show
 :info instance Show

 where

 :info Show

 displays information about everything called Show

 I know that classes and types share the same namespace currently, but it  
 might not always be so.

Sounds good in principle, and has the advantage of being 100%
backward compatible, but :i class Show for the common case
(ahum, _my_ common case at least ;) still seems rather verbose,
so how to abbreviate that?

Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-09 Thread Remi Turk
On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
 On 2009 Feb 5, at 5:49, Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set of  
 commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show
 (...)
 However, it would make :i ambiguous, which is rather sad.

 :class Show -- unique prefix :cl, already many such collisions
 :instance Show

That could work, but then how to get information about types as
opposed to classes? Its not in the above example, but Show
actually stands for an arbitrary typeclass _or type_.

However, as igloo pointed out on the ticket, abbreviations don't
actually have to be unique:

 For example, :b means :break even though we also have :back, :browse and 
:browse!.  [1]

That would personally lead me to prefer the :info/:instances
combo, with :i as an abbreviation of :info.

Groeten, Remi

[1] http://hackage.haskell.org/trac/ghc/ticket/2986#comment:4
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-06 Thread Remi Turk
On Thu, Feb 05, 2009 at 12:35:43PM +0100, Peter Hercek wrote:
 Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set of 
 commands:

:info Show-- See class definition only
:instances Show   -- See instances of Show

 Hi Remi,

 If you do not want to wait till this is implemented you can do it  
 yourself using ghci scripting.

Thank you Peter, but in this case it won't be of much help:
I am already running a patched GHCi:
http://hackage.haskell.org/trac/ghc/attachment/ticket/2986/ghci-info-no-instances.patch
But I may use it for something else later, so thanks anyway!

Cheers, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


:info features

2009-02-05 Thread Remi Turk
One of my most used GHCi commands is :info, but quite often
the type or class definitions that I'm interested in get drowned
in lots of instances.

So a week ago I wrote a feature request and a little patch that
allowed the following:

   :info Show -- See class definition and instances
   :info -Show-- See class definition only

SPJ agreed with the idea itself, but suggested an alternative set of commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show

This would have the advantage of making it easier to later add
additional features:

   :instances Show (Tree _)   -- See instances of form (Show (Tree ...))

However, it would make :i ambiguous, which is rather sad.

Another potential addition to :info (or another command) would be
evaluating types to their normal form, that is, expanding
(associated) type synonyms. E.g.:

   :typeeval Plus (Suc Zero) (Suc Zero)   -- (Suc (Suc (Suc (Suc Zero

Again, the question is whether this is really useful
(or reasonably easy to implement, SPJ?) and if so, what interface
is to be preferred?

So what's your favourite syntax? One of these options or something else?
Or are these features completely unnecessary?

Oh, the ticket can be found at
http://hackage.haskell.org/trac/ghc/ticket/2986#comment:3

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: type families not advertised for 6.8

2007-10-20 Thread Remi Turk
On Fri, Oct 19, 2007 at 08:25:22AM +0100, Simon Peyton-Jones wrote:
 | What does this imply for 6.8 support for FD's, as they now use
 | the same type-coercions?
 
 Actually FDs do not use type coercions, in GHC at least.  As Mark

Excuse me, it turns out I didn't look carefully enough: It's not
functional dependencies, it's classes-with-only-one-method:

module Bar where

bar = fmap id []

Compiles to the following Core with 6.8.0.20071002:

Bar.bar :: forall a_a5M. [a_a5M]
[GlobalId]
[]
Bar.bar =
  \ (@ a_a5M) -
(GHC.Base.$f8
 `cast` ((GHC.Base.:Co:TFunctor) []
 :: (GHC.Base.:TFunctor) []
  ~
forall a_a5G b_a5H. (a_a5G - b_a5H) - [a_a5G] - [b_a5H]))
  @ a_a5M @ a_a5M (GHC.Base.id @ a_a5M) (GHC.Base.[] @ a_a5M)


Or does this simply mean that only type-functions (the type/axiom
stuff) is not supported in 6.8, but type coercions (~ and cast) are supported
(although perhaps not at the source level)?

Cheers, Remi

 originally described them, FDs guide inference; and in
 particular, they give rise to some unifications that would not
 otherwise occur.  In terms of the intermediate language, that
 means there is no evidence associated with a FD; it's just the
 type checker's business. That means that various
 potentially-useful things can't be expressed, notably when FDs
 are combined with existentials or GADTs, that involve *local*
 equalities, which were beyond the scope of Marks's original
 paper.
 
 As the recent thread about FDs shows, FDs are quite tricky, at
 least if one goes beyond the well-behaved definition that Mark
 originally gave.  (And FDs are much more useful if you go
 beyond.)
 
 Our current plan is to regard FDs as syntactic sugar for indexed
 type families.  We think this can be done -- see our IFL workshop
 paper http://research.microsoft.com/%7Esimonpj/papers/assoc-types
 
 No plans to remove them, however.  After all, we do not have much
 practical experience with indexed type families yet, so it's too
 early to draw many judgements about type families vs FDs.
 
 I recommend Iavor's thesis incidentally, which has an interesting
 chapter about FDs, including some elegant (but I think
 unpublished) syntactic sugar that makes a FD look more like a
 function.  I don't think it's online, but I'm sure he can rectify
 that.
 
 Simon
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: type families not advertised for 6.8

2007-10-18 Thread Remi Turk
On Thu, Oct 18, 2007 at 02:58:21AM +0100, Simon Peyton-Jones wrote:
 |  Absolutely not; quite the reverse.  It means that some of the *code* for
 | type functions happens to be in the 6.8 release --- but that code has bugs.
 | It's only in 6.8 for our convenience (to avoid too great a divergence 
 between
 | the HEAD and 6.8), but we do not plan to *support* type functions in 6.8.
 | Doing that would delay 6.8 by 3 months.
 |
 | Do you make any difference between associated type synonyms and type
 | functions in this respect?
 
 No difference: both are in the 6.8 code base, but we won't
 support them there.  Both are in the HEAD, and we will support
 them there.
What does this imply for 6.8 support for FD's, as they now use
the same type-coercions?

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: STM and unsafePerformIO

2005-08-03 Thread Remi Turk
On Wed, Aug 03, 2005 at 12:50:54PM +0200, Robert van Herk wrote:
 Hello All,
 
 I think I've read somewhere that STM doesn't like unsafePerformIO. 
 However, I would like to use a global STM variable. Something like this:
 
 module Main where
 import GHC.Conc
 import System.IO.Unsafe
 
 tSid = unsafePerformIO (atomically (newTVar 0))
 
 tickSessionID :: STM Int
 tickSessionID =
  do sid - readTVar tSid
 writeTVar tSid (sid + 1)
 return sid
 
 main = atomically tickSessionID
 
 
 
 But, when I try this, the evaluation of main causes a segmentation 
 fault. Is there a workaround for this bug?
 
 Regards,
 Robert

It probably dies not because of unsafePerformIO per se, but
because STM doesn't understand nested transactions, and
unsafePerformIO here results in a nested transaction. Using the
following main works for me, as it forces both atomically's to
be evaluated sequentially:

main = tSid `seq` atomically tickSessionID


See also
http://haskell.org/pipermail/glasgow-haskell-users/2005-June/008615.html
and
http://sourceforge.net/tracker/index.php?func=detailaid=1235728group_id=8032atid=108032

Happy hacking,
Remi

P.S. Could you find out (and fix) what inserts those spurious *'s in your code?

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Remi Turk
On Fri, Jun 10, 2005 at 07:32:42PM +0200, Lennart Augustsson wrote:
 Andre Pang wrote:
 G'day all,
 
 Just looking at the documentation for System.IO.unsafeInterleaveIO,  
 what exactly is unsafe about it?
 You pick. :)
 
 It can break referential transparency.  It can break type safety.
 
   -- Lennart
 

Are you sure you're not talking about unsafePerformIO?

System.IO.Unsafe.unsafePerformIO:: IO a - a
System.IO.Unsafe.unsafeInterleaveIO :: IO a - IO a

As far as I know unsafeInterleaveIO in general isn't any unsafer
than it's special cases getContents / hGetContents / readFile /
getChanContents.  Although fighting lazy IO might occasionally
drive someone mad, which could arguably be called unsafe.

Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpxOF8lzrZuS.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Remi Turk
On Sat, Jun 11, 2005 at 01:55:57AM +0200, Thomas Jäger wrote:
  Just looking at the documentation for System.IO.unsafeInterleaveIO,
  what exactly is unsafe about it?
 
 It can create pure values that trigger side effects during their
 evaluation. This can be abused to do IO outside of an IO monad
 (actually, hGetContents can already be used for that purpose).
 
 In the worst case, it can even crash the RTS:
  import Control.Concurrent.STM
  import System.IO.Unsafe
  
  main :: IO ()
  main = atomically = unsafeInterleaveIO (atomically $ return $ return ())
 
 Thomas

Stares at a core-dump.
I wonder whether this would be worth a bug-report, or perhaps a
warning in STM's docs about (understandable) undefined behaviour
in this case. Interestingly, Tomasz Zielonka's FakeSTM [1]
survives it.

Groeten,
Remi

[1]
http://www.haskell.org/pipermail/haskell-cafe/2005-March/009389.html
darcs get http://www.uncurry.com/repos/FakeSTM/

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpKdFyzGrO2R.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldr f (head xs) xs is not the same as foldr1 f xs

2005-05-08 Thread Remi Turk
On Sun, May 08, 2005 at 08:14:30PM +0200, David Sabel wrote:
 Hi!
 
 A small example for the claim mentioned in the subject:
 
 Prelude let x = 1:undefined in foldr (curry fst) (head x) x
 1
 Prelude let x = 1:undefined in foldr1 (curry fst)  x
 *** Exception: Prelude.undefined
 
 Perhaps it would be better to change the implementation of foldr1?

Why? *wonders what he's missing* It sounds like a rather silly
claim to me. When changed to

  foldr f (head xs) (tail xs)  is not the same as foldr1 f xs
^

I would be more interested to see examples...

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 6.4

2005-03-11 Thread Remi Turk
On Fri, Mar 11, 2005 at 12:25:04PM -, Simon Marlow wrote:
 
=
 The (Interactive) Glasgow Haskell Compiler -- version 6.4
=
 
 The GHC Team is delighted to announce a new major release of GHC.  It
 has been a long time since the last major release (Dec 2003!), and a
 lot has happened:

It's great to hear that *my computer isn't going to get much
sleep tonight* :)

And there's a funny typo which left me wondering why? for a few
seconds on
http://haskell.org/ghc/docs/6.4/html/users_guide/release-6-4.html

o Debug.QuickCheck is now Text.QuickCheck

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: infix type operators

2005-03-09 Thread Remi Turk
[warning: Very Vague message  possible bug-report follow]

Though I cannot claim any real-world experience with arrows, I'm
not sure I like this, and I hope they'll at least remain
experimental (may be removed next release kind of thing) for a
while.

- I doubt whether the difference between Arrow a = a b c and
  Arrow (~) = b ~ c is all that great. Or even, whether the
  perhaps slightly improved readability of b ~ c makes up for
  the IMO slightly decreased readability of Arrow (~).
- When one really needs to do it infix, one can always write
  Arrow a = b `a` c.
- It's one thing more to learn. The difference between types and
  typevariables (upper/lowercase) is better visible than the
  difference between operator(variables) and infix-types (Does
  it start with a colon?) Which, I have to admit, is more of a
  vague feeling than anything like a fact.
- We already have the special case of - as a _type_, not
  a typevariable, and having - as a type, :- as a type and -:
  as a typevariable doesn't sound too great. Of course, as - is
  special in expression context too, that may not be convincing
  either :(

So I guess I'll have to end this mail with there is at least one
person not feeling entirely comfortable about it :)

Would it at least be possible to make it a seperate flag from
-fglasgow-exts? (I'm slightly worried about people needing one
extension and then using the rest too just because they're
already enabled, so actually this doesn't apply only to this
particular feature.)

Groetjes,
Remi


On Wed, Mar 09, 2005 at 05:06:03PM -, Simon Peyton-Jones wrote:
 OK, it's done for 6.4
 
 SImon
 
 | -Original Message-
 | From: [EMAIL PROTECTED]
 [mailto:glasgow-haskell-users-
 | [EMAIL PROTECTED] On Behalf Of Ross Paterson
 | Sent: 08 March 2005 16:29
 | To: glasgow-haskell-users@haskell.org
 | Subject: infix type operators
 | 
 | The User's Guide says:
 | 
 | The only thing that differs between operators in types and
 | operators in expressions is that ordinary non-constructor
 | operators, such as + and * are not allowed in types.  Reason:
 | the uniform thing to do would be to make them type variables,
 | but that's not very useful.  A less uniform but more useful
 thing
 | would be to allow them to be type constructors.  But that gives
 | trouble in export lists.  So for now we just exclude them.
 | 
 | Conal has pointed out that the uniform thing would be useful for
 | general arrow combinators:
 | 
 | liftA2 :: Arrow (~) =
 | (a - b - c) - (e ~ a) - (e ~ b) - (e ~ c)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: segfault/massive memory use when using Data.Bits.shiftL

2005-02-28 Thread Remi Turk
On Mon, Feb 28, 2005 at 02:55:56PM +, Ganesh Sittampalam wrote:
 Hi,
 
 The following either eats memory until killed or segfaults (I can't pin
 down a reason for the difference). Tested with GHC 6.2.2 and 6.4.20050212,
 with various different libgmp3s under various Redhat and Debian platforms,
 and WinXP.
 
 Prelude :m +Data.Bits
 Prelude Data.Bits 18446658724119492593 `shiftL` (-3586885994363551744) ::
 Integer
 
 Cheers,
 
 Ganesh

shiftL for Integer is defined in fptools/libraries/base/Data/Bits.hs:

class Num a = Bits a where
shiftL   :: a - Int - a
x `shiftL` i = x `shift`  i

instance Bits Integer where
   shift x i | i = 0= x * 2^i
 | otherwise = x `div` 2^(-i)

IOW, for y  0:
x `shiftL` y
  = x `shift` y
  = x `div` 2^(-y)

and calculating, in your case, 2^3586885994363551744 is not
something your computer is going to like...
as it's probably a number which doesn't fit in our universe :)
Still, a segfault might point at a bug, which I unfortunately
won't be able to say much about. (Due to lack of knowledge 
information.)

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: segfault/massive memory use when using Data.Bits.shiftL

2005-02-28 Thread Remi Turk
On Mon, Feb 28, 2005 at 10:59:32PM +, Ganesh Sittampalam wrote:
 On Mon, 28 Feb 2005, Remi Turk wrote:
 
  On Mon, Feb 28, 2005 at 02:55:56PM +, Ganesh Sittampalam wrote:
  
   Prelude :m +Data.Bits
   Prelude Data.Bits 18446658724119492593 `shiftL` (-3586885994363551744) ::
   Integer
 
  and calculating, in your case, 2^3586885994363551744 is not
  something your computer is going to like...
  as it's probably a number which doesn't fit in our universe :)
 
 Hmm, good point. I hadn't thought about the fact that the number of digits
 in the answer would be rather large...
Actually, the final answer will be 0: It's only the intermediate
value that gets ridiculously large.

  Still, a segfault might point at a bug, which I unfortunately
  won't be able to say much about. (Due to lack of knowledge 
  information.)
 
 My googling suggests that gmp is prone to segfaulting when things get too
 large for it, so I'll just chalk it up to that.
 
 I apologise for thinking this was a bug :-)

No need to apologize. Segfaults _are_ IMHO almost always bugs.
And in this case too, though the fault isn't GHCs.

Groeten,
Remi

 Cheers,
 
 Ganesh

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Infix typeconstructors shown as prefix

2005-02-20 Thread Remi Turk
Hi,

with the following definitions

{-# OPTIONS -fglasgow-exts #-}
data a :++: b
class a :--: b

ghci prints the infix type(classe)s as prefix:

*Main :i :++:
data :++: a b   -- Defined at foo.hs:2:7

*Main :i :--:
class :--: a b where-- Defined at foo.hs:3:8

or (a real-world example):

*Main :t fac (One:@Zero:@Zero)
fac (One:@Zero:@Zero) :: :@ (:@ (:@ (:@ One One) Zero) Zero) Zero

Is this a bug, a feature or just Not Implemented Yet(TM)?

Groeten,
Remi

P.S. Are infix class-names a documented extension at all?

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
Hi,

when compiling the new ghc pre-releases made my gcc 2.95.3 die
with internal compiler error, I tried to compile it with gcc
3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
died, compiled+installed gcc 3.4.3, tried again, say it die again
and only then noticed it was actually still using 2.95.3 ;) but
had quite some difficulty to actually get it to compile with, in
my case, /usr/local/bin/gcc3

When using the following command-line

CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl --prefix=/var/tmp/ghc 
--with-gcc=/usr/local/bin/gcc3

stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc that's 
documented)

I had to prepend a custom directory with `gcc' a symlink to
`/usr/local/bin/gcc3' to its PATH to be able to compile the thing.

Is there any other/better way?

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 04:48:54AM -0700, Seth Kurtzberg wrote:
 Simon Marlow wrote:
 
 On 17 February 2005 11:12, Remi Turk wrote:
 
  
 
 when compiling the new ghc pre-releases made my gcc 2.95.3 die
 with internal compiler error, I tried to compile it with gcc
 3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
 died, compiled+installed gcc 3.4.3, tried again, say it die again
 and only then noticed it was actually still using 2.95.3 ;) but
 had quite some difficulty to actually get it to compile with, in
 my case, /usr/local/bin/gcc3
 
 When using the following command-line
 
 CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
 --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
 
 stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
 that's documented) 

 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
  
 
 This is a known problem in all the 3.x compilers, and also occurs, 
 although less often, with 2.9x versions.  I've seen no difference in 
 frequency comparing FreeBSD to Linux and NetBSD.
 
 The only solution, which is of course highly annoying, is to simply 
 restart the make.  For whatever reason this always works, sometimes 
 until the end of the build, and sometimes until some other crash.  My 
 theory is that it is related to the temporary files that gcc creates, 
 mostly for templates. 
 
 While a royal PITA, the resulting code is correct.
 
 Cheers,
  Simon

I'm afraid finding a workaround for compilers dying on
compiler-generated code isn't going to be much fun...

Anyway, I just replaced a
ifneq $(INSTALL_LIBS) 
by
ifneq $(strip $(INSTALL_LIBS)) 
(see my glasgow-haskell-bugs message of today, this usage is
recommended in make's info for strip.)

Now I could install ghc, remove the build-tree and get enough
free space to start compiling again.
This time I'll log everything and come back when I'm sure what
exactly is going on. (As I remember that 1) --with-gcc doesn't
do what it should and 2) the gcc-2.95-crash on linux seems to be
repeatable.)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 05:05:18AM -0700, Seth Kurtzberg wrote:
 Remi Turk wrote:
 I'm afraid finding a workaround for compilers dying on
 compiler-generated code isn't going to be much fun...
 
 Anyway, I just replaced a
ifneq $(INSTALL_LIBS) 
 by
ifneq $(strip $(INSTALL_LIBS)) 
 (see my glasgow-haskell-bugs message of today, this usage is
 recommended in make's info for strip.)
 
 Now I could install ghc, remove the build-tree and get enough
 free space to start compiling again.
 This time I'll log everything and come back when I'm sure what
 exactly is going on. (As I remember that 1) --with-gcc doesn't
 do what it should and 2) the gcc-2.95-crash on linux seems to be
 repeatable.)
 
  
 
 I'm not positive about 2.95, but I know that on 3.x it crashes in 
 different places, and even compiling different source files.  With each 
 3.x release, they fix some of them, but others pop up to take their 
 place.  Clearly the gcc people don't know what's going on.

Sounds like it just was about time to get a C-- backend ;o)

[off-topic] Btw, how bad is it to get Bad eta expand warnings
during compilation of GHC?

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 11:29:41AM -, Simon Marlow wrote:
 On 17 February 2005 11:12, Remi Turk wrote:
 
  when compiling the new ghc pre-releases made my gcc 2.95.3 die
  with internal compiler error, I tried to compile it with gcc
  3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
  died, compiled+installed gcc 3.4.3, tried again, say it die again
  and only then noticed it was actually still using 2.95.3 ;) but
  had quite some difficulty to actually get it to compile with, in
  my case, /usr/local/bin/gcc3
  
  When using the following command-line
  
  CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
  --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
  
  stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
  that's documented) 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
 
 Cheers,
   Simon

I seem to have been mistaken. When configuring with --with-gcc it
does use gcc 3.4.3. I'm letting it continue till completion to be
entirely sure. (As IIRC the compiler-errors came rather late in
the build and it's only compiling for about an hour now.)

I'll try to reproduce the 2.95 internal compiler error later.

Btw, at first I misunderstood the following comment in
docs/building/building.xml to mean that --with-gcc only specified
the compiler for actual .c files in the ghc-distribution. (Which
explains my (okay, for --with-gcc that's documented))

termliteral--with-gcc=parameterpath/parameter/literal
  
indextermprimaryliteral--with-gcc/literal/primary/indexterm
/term
listitem
  paraSpecifies the path to the installed GCC. This
  compiler will be used to compile all C files,
  emphasisexcept/emphasis any generated by the
  installed Haskell compiler, which will have its own
  idea of which C compiler (if any) to use.  The
  default is to use literalgcc/literal./para
/listitem

To be more precisely, to me the installed Haskell compiler was
the (stage[12] of the) Haskell compiler to be installed once
it's compiled.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
[Resent, with a few #ifdef FOO's removed from the body (still in
the attachement, and using gzip instead of bzip2 to prevent
awaiting moderation ;)]

On Thu, Feb 17, 2005 at 11:29:41AM -, Simon Marlow wrote:
 On 17 February 2005 11:12, Remi Turk wrote:
 
  when compiling the new ghc pre-releases made my gcc 2.95.3 die
  with internal compiler error, I tried to compile it with gcc
  3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
  died, compiled+installed gcc 3.4.3, tried again, say it die again
  and only then noticed it was actually still using 2.95.3 ;) but
  had quite some difficulty to actually get it to compile with, in
  my case, /usr/local/bin/gcc3
  
  When using the following command-line
  
  CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
  --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
  
  stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
  that's documented) 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
 
 Cheers,
   Simon

In case you've got nothing else left to do.. ;)

The ghc command which perfectly repeatable kills gcc:

make[2]: Entering directory `/var/tmp/ghc-6.4.20050216/ghc/compiler'
../../ghc/compiler/stage1/ghc-inplace -H16m -O  -istage2/utils  
-istage2/basicTypes  -istage2/types  -istage2/hsSyn  -istage2/prelude  
-istage2/rename  -istage2/typecheck  -istage2/deSugar  -istage2/coreSyn  
-istage2/specialise  -istage2/simplCore  -istage2/stranal  -istage2/stgSyn  
-istage2/simplStg  -istage2/codeGen  -istage2/main  -istage2/profiling  
-istage2/parser  -istage2/cprAnalysis  -istage2/compMan  -istage2/ndpFlatten  
-istage2/iface  -istage2/cmm  -istage2/nativeGen  -istage2/ghci -Istage2 -DGHCI 
-package template-haskell -package unix -package readline -DUSE_READLINE 
-package Cabal -cpp -fglasgow-exts -fno-generics -Rghc-timing -I. -IcodeGen 
-InativeGen -Iparser -recomp -Rghc-timing  -H16M '-#include hschooks.h'-c 
cmm/MachOp.hs -o stage2/cmm/MachOp.o  -ohi stage2/cmm/MachOp.hi
/tmp/ghc32662.hc: In function `s5dU_ret':
/tmp/ghc32662.hc:11210: Internal compiler error in `build_insn_chain', at 
global.c:1756

The dying gcc command:

gcc -x c cmm/MachOp.hc -o /tmp/ghc15388.raw_s -DDONT_WANT_WIN32_DLL_SUPPORT 
-fno-defer-pop -fomit-frame-pointer -fno-builtin -DSTOLEN_X86_REGS=4 -S 
-Wimplicit -O -D__GLASGOW_HASKELL__=604 -ffloat-store -I cmm -I stage2 -I . -I 
codeGen -I nativeGen -I parser -I 
/var/tmp/ghc-6.4.20050216/libraries/readline/include -I 
/var/tmp/ghc-6.4.20050216/libraries/unix/include -I 
/var/tmp/ghc-6.4.20050216/libraries/base/include -I 
/var/tmp/ghc-6.4.20050216/ghc/includes

The (naively) relevant part of the generated HC-file appears to
be the next function (with some code which doesn't seem to
matter for the crash removed). I have no idea whether this is of any
help for nailing this kind of nastiness down, so I'm not going to
spend more of my night on it ;)

I did attach the complete failing HC-file.

Greetings,
Remi

// compile The Killing Line
#define BAR 1
IF_(s5dU_ret) {
W_ _c5ec;
FB_
#if BAR
if (_c5ec  0x5) goto _c5en;
#endif
_c5eo:
_c5eu:
R1.p = (P_)(W_)GHCziBase_True_closure;
Sp=Sp+1;
JMP_((*((P_)((*Sp) + (-0x14 + (*Sp));
_c5en:
switch (_c5ec) {
case 0x0: goto _c5eo;
case 0x1: goto _c5eo;
case 0x2: goto _c5eu;
case 0x3: goto _c5eo;
case 0x4: goto _c5eo;
}
FE_
}

-- 
Nobody can be exactly like me. Even I have trouble doing it.


MachOp.hc.bz2
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-16 Thread Remi Turk
On Thu, Feb 10, 2005 at 01:11:48PM -, Simon Marlow wrote:
 We are finally at the release candidate stage for GHC 6.4.  Snapshots
 with versions 6.4.20050209 and later should be considered release
 candidates for 6.4.
 
 Source and Linux binary distributions are avaiable here:
 
   http://www.haskell.org/ghc/dist/stable/dist/
 
 Please test if you're able to, and give us feedback.
 
 Thanks!
 
 Simons  the GHC team

Hi,

I just noticed that in GHC.PArr, productP is defined wrongly

productP :: (Num a) = [:a:] - a
productP  = foldP (*) 0

in (the likely) case that PArr is deprecated, you may want to add
a DEPRECATED-pragma.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: STM check/MonadPlus

2005-02-07 Thread Remi Turk
On Mon, Feb 07, 2005 at 10:53:36AM -, Simon Peyton-Jones wrote:
 Thanks for the typo.  Yes, for Haskell guys 'guard' is fine; but the
 main audience for the paper is non-haskell folk, so we have to spell out
 the defn.
 
 S

Hm, what about calling it `guard' and adding a footnote saying
that in Haskell its type is actually more general? It smells a
bit like namespace pollution to me right now. (Says he who hasn't
even compiled 6.3 since STM got in ;)

Groetjes,
Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: getUserEntryForName weirdness

2004-10-29 Thread Remi Turk
On Fri, Oct 29, 2004 at 06:29:52PM +0200, Peter Simons wrote:
 Is anyone else seeing this on his system?
 
   getUserEntryForName [] = print . userName
   wasabi
 
 wasabi happens to be the last entry in the /etc/passwd
 file, and that is what I get every time I query for an user
 that doesn't exist. The source code promises an exception,
 but I don't get one. 
 
 Peter

Prelude System.Posix.User getUserEntryForName [] = print .  userName
*** Exception: getUserEntryForName: does not exist (No such file
or directory)

linux 2.4.26, ghc 6.2.1, compiled with gcc 3.4.1 IIRC.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-11 Thread Remi Turk
On Wed, Aug 11, 2004 at 02:27:19PM +0100, Simon Marlow wrote:
 On 10 August 2004 16:04, Remi Turk wrote:
  http://www.haskell.org/pipermail/glasgow-haskell-users/2004-June/006767.html
 
 Hmm yes, I now realise that it's not quite as easy as I implied in that
 message.  The problem is the memory allocation.  If a GMP function
 allocates some memory, we have to swizzle the pointer that comes back
 (where swizzle(p) { return p-sizeof(StgArrWords) }).  Unfortunately you
 have to do this without giving the GC a chance to run, and there's no
 way to get this atomicity in plain Haskell+FFI, which is why the primops
 are still necessary.
 
 Perhaps one way to do it would be to define generic Integer primop
 wrappers - i.e. one wrapper for an mpz function that takes two arguments
 and returns one, etc.  The primop implementations already work like
 this, except that the wrappers are CPP macros.  If the wrapper were
 lifted to the level of a primop itself, then you could easily use
 different mpz functions by calling the appropriate primop passing the
 address of the mpz function.

Ah, the shockingly inefficient family of GMP_TAKEx_RETy macros ;)
(I understand the swizzle-talk only partly, so I'll ignore it and
hope my words won't turn out to be utter nonsense..)

But as long as GMP doesn't mind about being abused the way my
most recent util.c does, I can get away with the
mp_set_memory_functions-trick, can't I?
(*Be sure to call `mp_set_memory_functions' only when there are no
active GMP objects allocated using the previous memory functions!
Usually that means calling it before any other GMP function.*,
and using undocumented features)

And with this trick and a ffi GMP-binding implement a working Mpz
datatype.

And when (if?) this is done, drop in a type Mpz = Integer, rip
out all Integer-primops, remove the mp_set_memory_functions-trick
and start benchmarking?
(Conveniently forgetting that fromInteger :: Integer - Integer
most certainly has to stay a primop anyway...)

Or is the rts using Integers in such a way that any (standard
malloc) allocations are forbidden while e.g. (*) :: Integer -
Integer - Integer is running?

 Cheers,   
   Simon

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-10 Thread Remi Turk
On Tue, Aug 10, 2004 at 12:59:46PM +0100, Simon Marlow wrote:
 GHC's use of GMP does cause problems if you want to use GMP for your own
 purposes, or if you link with external code that wants to use GMP.  The
 real problem is that GMP has internal state, which means it can't be
 used in a modular way.  But there's not much we can do about that.
 
 Possibilities:
 
   - Rename all the symbols in our GMP to be unique. (sounds hard)
and ugly

   - Replace GMP with something else (someone is working on this, 
 I believe).
Do you have a pointer? It sounds interesting. *see below*

   - try to get two copies of GMP into your program by pre-linking
 the RTS with one copy, then linking the rest of the program
 with the other copy.  I'm being intentionally vague here - I
 feel that this ought to be possible, but it's an ugly hack
 at best.
I'm not sure I share your feelings about that ;) It sounds like
symbol-clash-hell. But quite possibly I'm just being ignorant.

   - reset GMP's memory allocators before calling it from your code,
 and set them back to the RTS allocators afterward.  Slow, but it
 should work.  It doesn't solve the problem properly though: external
 libraries which use GMP are still broken.
It does indeed seem to work, after a quick test. (new util.c attached)

And it does solve _my_ immediate problem: I can surround every
gmp-operation with a gmp_begin()/gmp_end() and pretend to be
happy. (and anyway, I'm just messing around, failure merely means
I've got yet another unfinished project ;))

Part of the reason for all this messy FFIing is your post:
http://www.haskell.org/pipermail/glasgow-haskell-users/2004-June/006767.html

If Integers where implemented via the FFI that would make it
quite a bit easier to special-case e.g. (^) and Show for Integer.
(IIRC, GMP's mpz-to-string recently got a huge speedup, it would
be nice if GHC would automagically profit of that..)

 Cheers,
   Simon
 

Happy hacking  keep up the good work ;)
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-10 Thread Remi Turk
On Tue, Aug 10, 2004 at 01:09:03PM +0100, Simon Marlow wrote:
 On 10 August 2004 13:03, MR K P SCHUPKE wrote:
 
  Re GMP, Why not provide more GMP functions as primitives on the
  Integer type, and avoid the need to call out to GMP via the FFI?
 
 Show us the code! :-p

Or implement Integers via the FFI, and make it much easier to
provide more GMP functions as primitives (that is: simple
foreign imports)

Which is what I was trying, until I bumped into those weird
memory problems I had almost forgotten existed ;)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHCI/FFI/GMP/Me madness

2004-08-09 Thread Remi Turk
Hi all,

I recently tried to create a ffi-binding to gmp in ghc, and
failed miserably. After a few days of debugging, simplifying the
code and tearing my hear out, I'm slightly completely stumped,
and crying for help ;)

In short: calling gmp-functions from GHCI *with a prompt between*
them seems to do Really Bad Things. (read: memory corruption)


The long story:
---

mpz_t p;

str_test()
{
gmp_printf(%Zd\n, p);
}

void mpz_new()
{
mpz_init_set_si(p, 1);
}

foreign import ccall mpz_new:: IO ()
foreign import ccall str_test   :: IO ()


Prelude Main mpz_new
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
142833060
Prelude Main str_test
142833060


Using other flags, importing extra modules, using CVS 6.3 (a few
weeks old) or not compiling it before loading it in GHCI slightly
changes the symptoms (other wrong numbers or make it happen
later/earlier) but copypasting the code from main some 10 to 20
times seems to be a sure way to reproduce it.

Simply running main doesn't seem to expose the problem.
Now of course, GHCI uses Integer-ops during it's REPL, which I
suspect is exactly what causes/exposes the problem.

Am I doing (Un)Officially Forbidden Things? Is it time for a
bug-report? Do I finally have to learn drinking coffee? ;)
I'd be delighted to know.

The full code is attached.

TIA,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
.PHONY: clean ghci

CC=gcc
CFLAGS=-Wall -g
GHCFLAGS=util.o -\#include util.h

main_src=PrimMpz.hs

ghci: util.o
ghci $(GHCFLAGS) $(main_src)

exe: util.o
ghc --make $(GHCFLAGS) $(main_src)

util.o: util.c
$(CC) $(CFLAGS) -c $

clean:
rm -f a.out *.o *.hi
{-# OPTIONS -fffi #-}
module Main where

foreign import ccall mpz_new:: IO ()
foreign import ccall str_test   :: IO ()

main= do
mpz_new
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
#include stdio.h

#include util.h

mpz_t p;

void str_test()
{
gmp_printf(%Zd\n, p);
}

void mpz_new()
{
mpz_init_set_si(p, 1);
}
#ifndef _UTIL_H
#define _UTIL_H

#include gmp.h

void str_test();
void mpz_new();

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


Re: GHCI/FFI/GMP/Me madness

2004-08-09 Thread Remi Turk
On Sun, Aug 08, 2004 at 07:34:04AM -0700, Sigbjorn Finne wrote:
 Hi,
 
 please be aware that the RTS uses GMP as well, and upon
 initialisation it sets GMP's 'memory functions' to allocate memory
 from the RTS' heap. So, in the code below, the global variable
 'p' will end up having components pointing into the heap.
 Which is fine, until a GC occurs and the pointed-to
 GMP allocated value is eventually stomped on by the storage
 manager for some other purpose.
 
 I'm _guessing_ that's the reason for the behaviour you're seeing.

Hm, I _was_ aware of mp_set_memory_functions being used by the RTS.
I've seen it often enough in ltrace's ;)
It does indeed sound rather plausible (and making big allocations
and such does indeed cause it to happen earlier).

At which point my next question is: what now? I don't feel really
confident about my GHC-hacking skills (huh? skills? where? ;) so
does that mean I'm out of luck?
*looks* Am I correct that I'd have to copy any GMP-allocated
memory to my own memory before returning from C and vice-versa?
I hope not :(

Happy hacking,
Remi 3212th unfinished project Turk

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-09 Thread Remi Turk
On Mon, Aug 09, 2004 at 01:09:40PM -0400, Abraham Egnor wrote:
 FWIW, I couldn't reproduce this problem on my system (i.e. str_test
 always printed 1).  GHC 6.2.1, libgmp 4.1.3, debian unstable
 
 Abe

Same versions here, on an old heavily-patched/FUBAR rock linux
1.4 system.

Does the following make any difference? (trying to cause GCing)

Haskell/Mpz/weird% make
ghci util.o -#include util.h PrimMpz.hs
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.2.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading object (static) util.o ... done
final link ... done
Compiling Main ( PrimMpz.hs, interpreted )
Ok, modules loaded: Main.
*Main mpz_new
*Main sum (replicate (200*1000) 0)
0
*Main str_test
1076535944
*Main 


Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users