
(i always forget to reply-to-all)
If you'd like to reference C functions with Strings, one possible way is to
use System.Posix.DynamicLinker and the wrapper over libffi that's been
uploaded to hackage recently:
[m@monire asdf]$ ghci
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.
ghci> :m + Foreign.LibFFI
ghci> :m + Foreign.Ptr Foreign.Storable
ghci> :m + Foreign.C.Types Foreign.C.String
ghci> :m + System.Posix.DynamicLinker
ghci> malloc <- dlsym Default "malloc"
Loading package unix-2.3.1.0 ... linking ... done.
ghci> syscall <- dlsym Default "syscall"
ghci> :! echo -ne "#include
On Friday 29 of May 2009 19:34:44 Patrick LeBoutillier wrote:
Hi all,
Is it possible with Haskell to call a function whose name is contained in a String? Something like:
five = call_func "add" [2, 3]
If not, perhaps this is acheivable using FFI?
Or maybe you are asking for template haskell[1]. With it you can actually generate function at compile time. It depends on waht you actually need.
{-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH
five = $( foldl appE (varE $ mkName "+") [ litE $ integerL 2 , litE $ integerL 3 ] )
[1] http://haskell.org/haskellwiki/Template_Haskell
-- Khudyakov Alexey _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe