This works ok with the current contents of the repository.

> -----Original Message-----
> From: Sven Panne [mailto:[EMAIL PROTECTED]]
> Sent: Thursday, January 28, 1999 3:23 PM
> To: [EMAIL PROTECTED]
> Subject: A continuing saga: foreign export dynamic
> 
> 
> Yesterday's ghc-4.02 dies during compilation of the following
> program. Without -O everything is OK.
> 
> ------------------------------------------------------------------
> module Foo where
> import Addr
> foreign export ccall dynamic bar :: IO () -> IO Addr
> ------------------------------------------------------------------
> panne@liesl: > ghc -c -fglasgow-exts -O Foo.hs
> 
> panic! (the `impossible' happened):
>       Missing alternative PrelStable.StablePtr{-r1ad,i-}
>                   (PrelStable.StablePtr{-6g,w-},
>                    [ds_s1tc],
>                    case {-_ccall-}__ccall createAdjustor {__a 
> (PrelGHC.State#{-3z,W-} PrelGHC.RealWorld{-3w,W-}
>                                                               
>  -> PrelGHC.Int#{-3e,W-}
>                                                               
>  -> PrelGHC.StablePtr#{-3x,W-} (PrelIOBase.IO{-3T,i-} 
> PrelBase.(){-40,W-})
>                                                               
>  -> PrelGHC.Addr#{-31,W-}
>                                                               
>  -> (# PrelGHC.State#{-3z,W-} PrelGHC.RealWorld{-3w,W-},
>                                                               
>        PrelGHC.Addr#{-31,W-} #))
>                                                           ds_s1t8 __Us
>                                                           1
>                                                           ds_s1tc
>                                                           
> (__litlit "d1tU" PrelGHC.Addr#{-31,W-})}
>                    of ds_s1th { (# ds_s1ti, ds_s1tg #) ->
>                    let { s_s1tk = PrelAddr.A#{-61,w-} {ds_s1tg}
>                    } in  (# ds_s1ti, s_s1tk #)
>                    })
> 
> Please report it as a compiler bug to 
> [EMAIL PROTECTED]
> 
> Done! :-)
> 
> Cheers,
>    Sven
> -- 
> Sven Panne                                        Tel.: 
> +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
> 

Reply via email to