[Haskell-cafe] compilation succeeds -- execution fails
Jason Dusek
jason.dusek at gmail.com
Fri Mar 28 14:33:52 EDT 2008
Thomas Schilling <nominolo at googlemail.com> wrote:
> Did you try removing all .hi and .o files?
Yes. I tried it again this morning, and I've got the same
error -- same unknown symbol, &c.
I don't have trouble with most Haskell programs on my Mac, so
I assume it's the way I'm connecting to C that is the problem.
I've pasted in the relevant code below my signature -- it
seems plain enough to me, but I've not done much with foreign
declarations.
The `Ptr Char` declarations, for example, point to things
which are actually C ints -- they are all valid Unicode code
points, so I figure there's no harm done.
--
_jsn
module Data.Char.CEDICT.Lists where
import Foreign
import Foreign.C
import Foreign.Storable
import Foreign.Marshal.Array
{-# INCLUDE "c/data.h" #-}
foreign import ccall unsafe "&" ts :: Ptr Char
foreign import ccall unsafe "&" ts_len :: Ptr Int
forTradSimp = pairUp $ readIn ts_len ts
foreign import ccall unsafe "&" st :: Ptr Char
foreign import ccall unsafe "&" st_len :: Ptr Int
forSimpTrad = pairUp $ readIn st_len st
readIn lenPtr arrPtr = unsafePerformIO $ peekArray len arrPtr
where
len = unsafePerformIO $ peek lenPtr
pairUp [] = []
pairUp [item] = []
pairUp (a:b:rest) = (a, b):(pairUp rest)
forLookup =
[ ("\64013",[("huo4","to vomit")])
, ("\64012",[("wu4","duplicate of Big Five A461")])
, ("\40868",[("xie2","to harmonize / to accord with / to agree")])
, ("\40866",[("he2","harmonious")])
]
More information about the Haskell-Cafe
mailing list