#2745: ghc -shared broken
---------------------------------+------------------------------------------
    Reporter:  simonmar          |       Owner:         
        Type:  bug               |      Status:  new    
    Priority:  high              |   Milestone:  6.10.2 
   Component:  Compiler          |     Version:  6.10.1 
    Severity:  normal            |    Keywords:         
  Difficulty:  Unknown           |    Testcase:         
Architecture:  Unknown/Multiple  |          Os:  Windows
---------------------------------+------------------------------------------
 Lennart reports that `ghc -shared` is broken:

 {{{
 $ cat Foo.hs
 {-# LANGUAGE ForeignFunctionInterface #-}
 module Foo where

 f :: Int -> Int
 f x = x+1

 foreign export ccall f :: Int -> Int

 $ ghc -shared Foo.hs
 Foo.o:fake:(.text+0x21): undefined reference to `stg_INTLIKE_closure'
 Foo.o:fake:(.text+0x28): undefined reference to `stg_ap_pp_info'
 Foo_stub.o:Foo_stub.c:(.text+0x9): undefined reference to `rts_lock'
 Foo_stub.o:Foo_stub.c:(.text+0x1a): undefined reference to `rts_mkInt'
 Foo_stub.o:Foo_stub.c:(.text+0x2e): undefined reference to `rts_apply'
 Foo_stub.o:Foo_stub.c:(.text+0x42): undefined reference to `rts_apply'
 Foo_stub.o:Foo_stub.c:(.text+0x55): undefined reference to `rts_evalIO'
 Foo_stub.o:Foo_stub.c:(.text+0x67): undefined reference to
 `rts_checkSchedStatus'
 Foo_stub.o:Foo_stub.c:(.text+0x72): undefined reference to `rts_getInt'
 Foo_stub.o:Foo_stub.c:(.text+0x7c): undefined reference to `rts_unlock'
 Foo_stub.o:Foo_stub.c:(.text+0x97): undefined reference to `getStablePtr'
 .....
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2745>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to