Skip to content

Instantly share code, notes, and snippets.

@niuk
Created January 26, 2012 11:46
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save niuk/1682404 to your computer and use it in GitHub Desktop.
Save niuk/1682404 to your computer and use it in GitHub Desktop.
This code will segfault.
{-# LANGUAGE
OverloadedStrings,
FlexibleInstances #-}
module Main where
import Prelude
import System.IO
import Control.Monad
import Data.String
import Foreign.Ptr
import Foreign.C.Types
import Foreign.C.String
import Foreign.Storable
import Foreign.Marshal.Alloc
import LLVM.FFI.Core hiding (typeOf, sizeOf)
import LLVM.FFI.ExecutionEngine
import LLVM.Target.Native
instance IsString (IO CString) where
fromString = newCString
main = do
linkInJIT
initializeNativeTarget
-- create the module
myModuleRef <- moduleCreateWithName =<< "myModule"
dumpModule myModuleRef
-- create a function that simply adds the two numbers
myFunctionName <- "myFunction"
argTypes <- mallocBytes (2 * sizeOf (undefined :: TypeRef))
pokeElemOff argTypes 0 int64Type
pokeElemOff argTypes 1 int64Type
myFunction <- addFunction myModuleRef myFunctionName (functionType int64Type argTypes 2 0)
myBlock <- appendBasicBlock myFunction =<< "myBlock"
myBuilder <- createBuilder
positionAtEnd myBuilder myBlock
temp <- buildAdd myBuilder (getParam myFunction 0) (getParam myFunction 1) =<< "myAdd"
buildRet myBuilder temp
-- create the execution engine
myEngineRefRef <- malloc
myErrorRef <- malloc
bad <- createJITCompilerForModule myEngineRefRef myModuleRef 0 myErrorRef
when bad (putStrLn =<< peekCString =<< peek myErrorRef)
myEngineRef <- peek myEngineRefRef
-- allocate space for the parameters: two 64-bit integers
args <- mallocBytes (2 * sizeOf (undefined :: GenericValueRef))
pokeElemOff args 0 =<< createGenericValueOfInt int64Type 42 0
pokeElemOff args 1 =<< createGenericValueOfInt int64Type 3 0
-- run the simple function
result <- runFunction myEngineRef myFunction 2 args
print $ genericValueToInt result 0
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment