[Haskell-cafe] How to execute a function loaded via GHCI.ObjLink?

Saurabh Nanda saurabhnanda at gmail.com
Thu Jul 27 14:20:47 UTC 2017


Hi,

I'm playing around with
https://www.stackage.org/haddock/lts-9.0/ghci-8.0.2/GHCi-ObjLink.html to
see if I can come up with some sort of hot-loading/plugin system in
Haskell.

I've managed to load a shared object (compiled from a Haskell source via
-rdynamic) with the following code:

    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE MagicHash, UnboxedTuples #-}

    module Main where

    import GHC.Exts         ( addrToAny# )
    import GHC.Ptr          ( Ptr(..) )
    import System.Info      ( os, arch )
    import Encoding
    import GHCi.ObjLink
    import Debug.Trace

    main :: IO ()
    main = do
      traceM "before initObjLinker"
      initObjLinker
      traceM "before loadObj"
      loadObj
"/Users/saurabhnanda/projects/test-plugins/test-plugins/app/PluginMarkup.o"
      traceM "after loadObj"

      -- NOTE: I've hardcoded the symbol name that I obtained from running
`symbols PluginMarkup.o`
      sym <- lookupSymbol "PluginMarkup_foliage_info"
      traceM "after lookupsymbol"
      traceM (show sym)

I'm getting the following output, which mean that I'm probably getting the
Ptr to the function.

    before initObjLinker
    before loadObj
    after loadObj
    after lookupsymbol
    Just 0x0000000104be49a8

Question is, how do I run the function in the same Haskell
environment/runtime? The underlying function is actually `foliage ::
UtcTime -> Html`

The code is available at
https://github.com/vacationlabs/hint-test/blob/dll/app/Main.hs and the DLL
is available at
https://github.com/vacationlabs/hint-test/blob/dll/app/PluginMarkup.o

-- Saurabh.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170727/62ad6a18/attachment.html>


More information about the Haskell-Cafe mailing list