#2841: Ghci + foreign export declarations result in undefined symbols
---------------------------------+------------------------------------------
    Reporter:  fasta             |        Owner:         
        Type:  bug               |       Status:  new    
    Priority:  normal            |    Milestone:  _|_    
   Component:  Compiler (FFI)    |      Version:  6.10.1 
    Severity:  major             |   Resolution:         
    Keywords:                    |   Difficulty:  Unknown
    Testcase:                    |           Os:  Linux  
Architecture:  Unknown/Multiple  |  
---------------------------------+------------------------------------------
Comment (by simonmar):

 please create a new ticket describing ''exactly'' the sequence of actions
 that lead to the error.  I haven't been able to reproduce the error you
 mentioned from the information you give above.

 {{{
 ~/scratch > cat 2841.hs
 {-# LANGUAGE ForeignFunctionInterface #-}
 module M2841 where

 -- save in a file New.hs

 foreign export ccall foo :: Int -> IO Int -- add this line and ghci will
 return something like New_stub.o: unknown symbol
 `Main_zdffoozuaIc_closure'

 -- if you first try without the line, it works. If you still have stub
 files in the current directory, it will fail with the same message as
 before.

 foo :: Int -> IO Int
 foo = return . length .  f

 f :: Int -> [Int]
 f 0 = []
 f n = n:(f (n-1))

 test = 1
 ~/scratch > ghc -c 2841.hs
 compilation IS NOT required
 ~/scratch > ghci 2841.hs
 GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 $HOME/.ghci
 Ok, modules loaded: M2841.
 Prelude M2841> foo 3
 3
 Prelude M2841> f 1
 [1]
 Prelude M2841> test
 1
 Prelude M2841>
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2841#comment:3>
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