[Glasgow-haskell-bugs] NCG name mangling

2000-10-04 Thread Sigbjorn Finne


Hi,

first time poster, long time listener :-) Possibly a known one, but the
NCG in 4.08.1 doesn't emit suitably decorated names when calling
out to 'foreign import'ed functions that use the stdcall calling convention,
e.g.,

sof$ cat foo.hs
module Foo { foreign import stdcall decorateMe :: IO () }
sof$ ghc-4.08.1 -S -c foo.hs -fglasgow-exts
sof$ grep 'call _decorate' foo.s
call _decorateMe
sof$ 

that should be 'call _decorateMe@0'

The function to use to decorate stdcall names is CallConv.decorateExtName.

--sigbjorn



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



Re: type of stToIO

2000-10-04 Thread Ross Paterson

On Wed, Oct 04, 2000 at 01:05:10PM +0200, Marcin 'Qrczak' Kowalczyk wrote:
: On Wed, 4 Oct 2000, Ross Paterson wrote:
: 
: > The library documentation says
: > 
: > stToIO :: ST s a -> IO a
: > 
: > but PrelIOBase says
: > 
: > stToIO :: ST RealWorld a -> IO a
: 
: AFAIR it's a different stToIO than one exported by the end-user module
: (IOExts or ST). Sorry, can't check it from here.

No, ST re-exports it from PrelIOBase.

: > The documented type would be unsafe (as it is in Classic Hugs), so it
: > seems necessary to mention the real world in the documentation.
: 
: Why is it unsafe? IMHO it is safe.

The following is accepted by hugs -98:

> import ST

> data Var v = Var { readVar :: IO v, writeVar :: v -> IO () }

> newVar :: v -> Var v
> newVar v = runST (do
> r <- newSTRef v
> return (Var {
> readVar = stToIO (readSTRef r),
> writeVar = \v' -> stToIO (writeSTRef r v')
> })
> )

> test :: Var Int -> Var Int -> IO ()
> test v1 v2 = do
> writeVar v1 3
> writeVar v2 4
> x <- readVar v1
> y <- readVar v2
> print x
> print y

> main = let v = newVar 0 in do
> test v v
> test (newVar 0) (newVar 0)

but the two tests do different things, breaking substitution.
GHC instantiates the state type variable to RealWorld, and then
complains

Inferred type is less polymorphic than expected
Quantified type variable `s' is unified with `RealWorld'
Signature type: forall s. ST s a
Type to generalise: ST RealWorld (Var v)

I think GHC is right and the library documentation wrong.




We're changing out ailing list software

2000-10-04 Thread Simon Marlow

Dear glasgow-haskell-users & glasgow-haskell-bugs,

At haskell.org we're going to be switching the mailing lists from majordomo
(which is somewhat old and clunky) to Mailman, which will amongst other
things make my life a lot easier, provide better archives, add digest
support and allow subscription/unsubscription via a web interface.

You should all receive a notification shortly about subscription to the new
lists.  Unfortunately it seems we have to do this, because the confirmation
contains the password for accessing & modifying your personal subscription
details on the web.  If you *don't* receive a confirmation in the next 24
hours, please let me know.

Heres hoping everything goes smoothly, and once again I apologise for the
extra spam in your mailbox.

Cheers,
Simon





Re: type of stToIO

2000-10-04 Thread Marcin 'Qrczak' Kowalczyk

On Wed, 4 Oct 2000, Ross Paterson wrote:

> The library documentation says
> 
>   stToIO :: ST s a -> IO a
> 
> but PrelIOBase says
> 
>   stToIO :: ST RealWorld a -> IO a

AFAIR it's a different stToIO than one exported by the end-user module
(IOExts or ST). Sorry, can't check it from here.

> The documented type would be unsafe (as it is in Classic Hugs), so it
> seems necessary to mention the real world in the documentation.

Why is it unsafe? IMHO it is safe.

-- 
Marcin 'Qrczak' Kowalczyk





type of stToIO

2000-10-04 Thread Ross Paterson

The library documentation says

stToIO :: ST s a -> IO a

but PrelIOBase says

stToIO :: ST RealWorld a -> IO a

The documented type would be unsafe (as it is in Classic Hugs), so it
seems necessary to mention the real world in the documentation.




RE: PPC port of ghc.

2000-10-04 Thread Simon Marlow

> I noticed that GHC mentions a powerpc AIX port.  I was 
> wondering what the
> difficulty would be in porting GHC to Linux-PPC.

Probably not too hard.  The PPC code is still there, but hasn't been tested
for a while (AFAIK, ghc 4.xx has never compiled on a PPC).  You may need to
extract some bits from ghc 3.xx's runtime system.

We'll certainly help out where possible, but I don't think any of us here
knows the PPC arch very well...

Cheers,
Simon