
29 May
2009
29 May
'09
12:41 p.m.
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