Hi,

A few days ago I uploaded on Hackage the first release of dynamic-linker-template package (System.Posix.DynamicLinker.Template). Basically, it uses Template Haskell to generate boilerplate code to dynamically load symbols of a shared library into a data defined using "record" syntax.

Simple example:

----------------------
{-# LANGUAGE TemplateHaskell, ForeignFunctionInterface #-}

import System.Posix.DynamicLinker.Template

data MyLib = MyLib {
    -- Mandatory field (name and type)
    libHandle :: DL,

    -- Mandatory symbol. Will throw an exception if not available
    myFunction1 :: Int -> Float,

     -- Optional symbol
    myFunction2 :: Maybe (Int -> Int)
}

$(makeDynamicLinker ''MyLib CCall 'id)

-- Use any String->String function instead of "id" to transform field names into symbol names

-- The following function will be generated:
-- loadMyLib :: FilePath -> [RTLDFlags] -> IO MyLib

main = do
    lib <- loadMyLib "mylib.so" [RTLD_NOW,RTLD_LOCAL]
    putStrLn $ show (myFunction1 lib 10)

----------------------

For a real world example (with the OpenCL library), see [1]. I don't use optional symbols yet but I will as I need to support different OpenCL versions that expose different symbols (some become deprecated and new releases add new ones). I use a custom function to transform field names into symbol names (to strip prefix). This functionality will also be useful with CUDA library which appends "_v2" to every symbol in recent releases...

Do not hesitate to report any bug or suggestion.

Cheers
Sylvain

[1] http://github.com/hsyl20/HViperVM/commit/26d512e924f7097e536351c412ea5986d3ed9654

--
Sylvain Henry
CS PhD Student at INRIA/LaBRI
University of Bordeaux (France)
sylvain.he...@inria.fr



_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to