I'm trying to follow along with the LLVM bindings tutorial here, and running into a segfault. The following code works in the sense that it prints a module header to output.ll, but it also segfaults somewhere.
module Main where
import Control.Monad.Error
import LLVM.General.Module
import LLVM.General.Context
import qualified LLVM.General.AST as AST
--Create and write out an empty LLVM module
main :: IO ()
main = writeModule (AST.defaultModule { AST.moduleName = "myModule" })
outputFile :: File
outputFile = File "output.ll"
writeModule :: AST.Module -> IO ()
writeModule mod = withContext $ (\context ->
liftError $ withModuleFromAST context mod (\m ->
liftError $ writeLLVMAssemblyToFile outputFile m))
--perform the action, or fail on an error
liftError :: ErrorT String IO a -> IO a
liftError = runErrorT >=> either fail return
I suspect this is related to the following hint from the linked tutorial:
It is very important to remember not to pass or attempt to use resources outside of the bracket as this will lead to undefined behavior and/or segfaults.
I think in this context the "bracket" is implemented by the withContext function, which makes it seem like everything should be handled.
If I change the definition of writeModule to
writeModule mod = do assembly <- (withContext $ (\context ->
liftError $ withModuleFromAST context mod moduleLLVMAssembly))
putStrLn assembly
that is, instead of writing to a file I just print out the string representation of the LLVM assembly, no segfault is thrown.
Does anyone have experience with these bindings? I'm also interested to know about the failure cases for the warning I quoted. That is, how would one "forget" not to use resources outside the bracket? All of the functions that seem to require a Context, well, require one. Isn't this kind of resource scoping issue exactly what Haskell is good at handling for you?
Version information:
llvm-general-3.4.3.0
LLVM version 3.4
Default target: x86_64-apple-darwin13.2.0
It would help if you shared your LLVM and cabal environment, LLVM is notorious for being backwards incompatible with itself so there might be an issue with using the latest versions of the bindings.
Behind the scenes writeLLVMAssemblyToFile is using a C++ call to do the file IO operation and I speculate that it's holding a reference to the LLVM module as a result of finalizing the file resource.
Try rendering the module to a String using moduleString and then only lifting into the IO monad to call writeFile from Haskell instead of going through C++ to the write.
import LLVM.General.Context
import LLVM.General.Module as Mod
import qualified LLVM.General.AST as AST
import Control.Monad.Error
main :: IO ()
main = do
writeModule (AST.defaultModule { AST.moduleName = "myModule" })
return ()
writeModule :: AST.Module -> IO (Either String ())
writeModule ast =
withContext $ \ctx ->
runErrorT $ withModuleFromAST ctx ast $ \m -> do
asm <- moduleString m
liftIO $ writeFile "output.ll" asm
The bindings can still rather brittle in my experience, you should ask on the issue tracker if the problem persists.
EDIT: This is a workaround for an old version that has been subsequently fixed. See: https://github.com/bscarlet/llvm-general/issues/109
Related
I have the following C function that I want to call from Haskell:
void read_params_for (property_list_t *props);
The function is supposed to receive some property_list_t and populate some values within it, so the caller then has an updated structure.
I have all the necessary wrappers for property_list_t (like Storable, etc.), but I can't figure out how to wrap this function into something like
readParamsFor :: ForeignPtr PropertyListT -> IO (ForeignPtr PropertyListT)
I tried using C2HS, and I also tried writing FFI bindings manually like:
foreign import ccall "read_params_for"
readParamsFor' :: Ptr PropertyListT -> IO ()
readParamsFor :: ForeignPtr PropertyListT -> IO (ForeignPtr PropertyListT)
readParamsFor ps = do
withForeignPtr ps $ \ps' -> do
res <- readParamsFor' ps'
pl <- newForeignPtr propertyListDestroy ps'
return pl
But in both cases, I get back my original "underpopulated" list.
How do I get an updated structure back to Haskell?
I realised that there was a bug in a C library that I wanted to use and that indeed, a simple withForeignPtr is sufficient if the bug is not there.
I'm currently trying to port parts of the Windows API to Haskell. One of the functions covered is SetConsoleCtrlHandler which registers a handler callback that is called whenever a Ctrl+C or Ctrl+Break is received from console input. So here a small sample program:
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Control.Monad
import GHC.ConsoleHandler
import Foreign
import System.Win32.Process
import System.Win32.Types
foreign import ccall "wrapper"
makeHandlerPtr :: (DWORD -> IO BOOL) -> IO (FunPtr (DWORD -> IO BOOL))
foreign import stdcall "windows.h SetConsoleCtrlHandler"
c_SetConsoleCtrlHandler :: FunPtr (DWORD -> IO BOOL) -> BOOL -> IO BOOL
main :: IO ()
main = unsafeCtrl
unsafeCtrl :: IO ()
unsafeCtrl = do
ptrHandler <- makeHandlerPtr $ \d -> do
putStrLn $ "received event " ++ show d
return True
c_SetConsoleCtrlHandler ptrHandler True
forM_ [1..50] $ \_ -> sleep 100
freeHaskellFunPtr ptrHandler
safeCtrl :: IO ()
safeCtrl = do
installHandler $ Catch $ \e -> do
putStrLn $ "received event " ++ show e
forM_ [1..50] $ \_ -> sleep 100
If you compile the above program via ghc --make AsyncCallback.hs and run the program, it crashes with the following error as soon as a control event is received:
$ AsyncCallback
AsyncCallback.exe: schedule: re-entered unsafely.
Perhaps a 'foreign import unsafe' should be 'safe'?
However, compiling with the -threaded option added seems to work fine:
$ AsyncCallback
received event 0
received event 1
received event 0
Not sure why this makes it work, as I don't explicitly use threads here, and I can't see where GHC would implicitly start a new thread.
Asking earlier about this on #haskell, someone noted that calling Haskell functions asynchronously from a C callback is inherently unsafe and that the above example just more or less coincidentally works. I was also pointed to GHC.ConsoleHandler.installHandler which seems to be a safe wrapper around SetConsoleCtrlHandler, and running the above program with main = safeCtrl indeed works fine. I tried to understand the implementation of installHandler (C-side and Haskell-side) but I don't quite get it.
The whole problem here seems to be that the callback is issued asynchronously, such that the Haskell RTS isn't "prepared" for when the callback tries to run the Haskell code. So I would like to know
How does the GHC implementation of installHandler work? What is the crucial part that makes that implementation work and my version fail?
Are there other options/general patterns how to call Haskell code asynchronously from a C callback? In this particular case, I can switch to the GHC implementation. But I may come accross similar C functions that asynchronously call back into Haskell code where I would have to write a safe binding on my own.
I have two LLVM.General.Module modules, A and B. My goal is to link B into A and then write the assembly to a file. I am playing for the moment with a toy program to see how to use the LLVM-General interface. I have used the LLVM-General-Pure package to create LLVM.General.AST modules for some compiler backends.
I would like to take these ASTs into the C++ world (LLVM.General.Module), link them, and then write the assembly. I found the error while linking the C++ modules, but I have a feeling that the error is in the way I produce the C++ objects. Here is what I did:
convASTToModE ast = do
a <- withContext $ \context -> do
x <- runErrorT $ withModuleFromAST context ast $ \mod -> return mod
return x
return a
Comment: I couldn't find a function of type Module -> Module (like moduleAST to make the AST from the C++ object when using, say withModuleFromLLVMAssembly) to give to withModuleFromAST, so that I get a Module back, so I just used the unit. My reading of this is that I can do something with the module I get from the ast, and I just want the module, so I just took it. I am guessing this is wrong, but figured it would do something.
When I execute this code on one of my LLVM.General.AST.Module modules, the code seems to run fine. But when I try to use it, it breaks. For example, if x is a LLVM.General.AST.Module, and I do
mod <- convASTToModE x
case mod of
Left _ -> error ""
Right mod' -> do
assemb <- moduleLLVMAssembly mod
putStrLn assemb
I get a segmentation fault.
LLVM-General-3.4.3.0
LLVM-3.4
UPDATE:
I tried the following:
writeASTToLLVMAssembly ast filename = do
withContext $ \context -> do
runErrorT $ withModuleFromAST context ast $ \mod -> do
runErrorT $ writeLLVMAssemblyToFile (File filename) mod
return ()
Gives:
*** Error in `./LLVMImportAndLinkTest': munmap_chunk(): invalid pointer:
0x00000000012db000 ***
Aborted (core dumped)
However,
showLLVMAssFromAST ast = do
str <- withContext $ \context -> do
str2 <- runErrorT $ withModuleFromAST context ast $ \mod -> do
str3 <- moduleLLVMAssembly mod
return str3
return str2
case str of
Left _ -> error "ast not convertible to string"
Right st -> return st
Gives no problems.
LLVM-General.3.4.3.0
LLVM-3.4
For example, with the LLVM.General.AST.Module found
http://lpaste.net/106407
That is the pretty printed version of the AST obtained by uploading
http://lpaste.net/106408
into LLVM-General.
That LLVM assembly was generated from Clang by compiling a C file.
Solution is to upgrade the version of llvm-general by changing the llvm-general dependency to llvm-general >= 3.4.3 which fixes a known bug in the implementation.
I have a module Target, with a function Target.accessMe inside it. I compile this module in some way, then get rid of the source code.
Now, what series of arcane incantations must I do to make a different program dynamically import Target.accessMe? This program knows accessMe's type in advance. Also, consider the fact that the source code of Target is not available.
The plugins package manages to accomplish this, but seems to have serious issues with working on Windows. I've checked out plugins's source, but am having trouble understanding it.
I've tried using Hint, but can only find out how to evaluate code that I have the source for.
Thanks for any help!
The answer to this question has been given to me elsewhere. The GHC API is capable of doing this. Here are two functions, one of which compiles Target.hs, while the other accesses Target.accessMe (and doesn't require the source code of the Target module to be there anymore).
import GHC
import DynFlags
compile :: String -> IO SuccessFlag
compile name = defaultRunGhc $ do
dynflags <- getSessionDynFlags
let dynflags' = dynflags -- You can change various options here.
setSessionDynFlags dynflags'
-- (name) can be "Target.hs", "Target", etc.
target <- guessTarget name Nothing
addTarget target
load LoadAllTargets -- Runs something like "ghc --make".
That's a function that compiles a given module and returns whether compilation succeeded or not. It uses a defaultRunGhc helper function that is defined as:
import GHC.Paths (libdir)
defaultRunGhc :: Ghc a -> IO a
defaultRunGhc = defaultErrorHandler defaultDynFlags . runGhc (Just libdir)
And now a function for fetching a value from the compiled module. The module's source code need not be present at this point.
import Unsafe.Coerce (unsafeCoerce)
fetch :: String -> String -> IO Int -- Assumes we are fetching an Int value.
fetch name value = defaultRunGhc $ do
-- Again, you can change various options in dynflags here, as above.
dynflags <- getSessionDynFlags
let m = mkModule (thisPackage dynflags) (mkModuleName name)
setContext [] [(m, Nothing)] -- Use setContext [] [m] for GHC<7.
fetched <- compileExpr (name ++ "." ++ value) -- Fetching "Target.accessMe".
return (unsafeCoerce fetched :: Int)
And that's it!
The plugins package is problematic anyway. You might want to look at Hint instead.
For a tool I'm writing ( http://hackage.haskell.org/package/explore ) I need a way to read haskell function definitions at run-time, apply them to values from my tool and retrieve the results of their application.
Can anyone give me a very basic example using GHC (6.10.4 or 6.12.1) API?
example function definition to be read from a file at run-time:
f x = 10**(4/1102*x - 1)
expected program output
--mapM_ print $ map f [428, 410, 389]
3.577165388142748
3.077536885227335
2.5821307011665815
!!UPDATE!!
I posted a quick answer but it creates an object file in the directory of execution, any tips to avoid this and avoid all file IO is most welcome. I want to also see a version that does everything in memory: user provides the function definition in a GUI for example and the compilation / evaluation does not create any object files.
Use hint. It's a GHCi-like wrapper around the GHC API that is not very difficult to use.
If you want an example of its use, I used it in my Yogurt project.
adapted from: http://www.bluishcoder.co.nz/2008/11/dynamic-compilation-and-loading-of.html
f.hs:
module Func (Func.f) where
f :: Double -> Double
f x = 10**(4/1102*x - 1)
main.hs:
import GHC
import GHC.Paths
import DynFlags
import Unsafe.Coerce
import Control.Monad
main :: IO ()
main =
defaultErrorHandler defaultDynFlags $ do
func <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget "f.hs" Nothing
addTarget target
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
m <- findModule (mkModuleName "Func") Nothing
setContext [] [m]
value <- compileExpr ("Func.f")
do let value' = (unsafeCoerce value) :: Double -> Double
return value'
let f = func
mapM_ print $ map f [428, 410, 389]
return ()
Nice work getting the API going. I can tell you a little bit about how the code generator works.
GHC uses the system assembler to create a .o file. If there is not an option available to get GHC to clean up after itself, then you should file a feature request against the API, using the bug tracker at http://hackage.haskell.org/trac/ghc/newticket?type=feature+request. In order to file the request, you will need to register an account.
Using the standard code generator, you will not be able to avoid file I/O entirely, just because GHC delegates the work of creating relocatable object code to the assembler. There is an experimental back end based on LLVM that might be able to do everything in memory, but I would be surprised if it is available in anything earlier than 6.13. However it could be worth asking on the GHC developers' list.