#2841: Ghci + foreign export declarations result in undefined symbols
-------------------+--------------------------------------------------------
Reporter: fasta | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (FFI)
Version: 6.10.1 | Severity: major
Keywords: | Testcase:
Os: Linux | Architecture: Unknown/Multiple
-------------------+--------------------------------------------------------
When using ghci and foreign export declarations, calling any function,
_even_ test, will result in an unknown symbol error.
Another bug is that the compiler is not purely functional in the sense
that without history (see below) it is possible for it to work in one
instance, but even then it doesn't. GHCi should have the property that if
X works in a state S of the OS (collection of files, etc), then it should
work in all states S', obtained by adding extra stuff to S, but not
modifying anything. Currently, GHCi is breaking this fundamental
property.
{{{
$ ghci New.hs
*Main> foo 1
<interactive>: New_stub.o: unknown symbol `Main_zdffoozuavi_closure'
}}}
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
-- 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
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2841>
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