You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
Hopefully the code below is self explanatory. Due to a lack on a Vector Generic instance, I cannot use simpleFunction on g. I also cannot see how to use fromVector.
{-# LANGUAGE DataKinds,ScopedTypeVariables #-}
import Data.TypeLevel.Num (D8)
import LLVM.Core
import LLVM.Util.Loop
import LLVM.Util.File
import LLVM.ExecutionEngine
f :: Value Float -> Value Float -> CodeGenFunction r (Value Float)
f = add
alterValue :: Value Float -> Value (Vector D8 Float) -> CodeGenFunction r (Value (Vector D8 Float))
alterValue x = mapVector (f x)
g :: CodeGenModule (Function (Float -> Vector D8 Float -> IO (Vector D8 Float)))
g = do
f <- createNamedFunction ExternalLinkage "g" $ \x img -> do
result <- alterValue x img
ret result
return f
myVec :: Vector D8 Float
myVec = toVector (45,89,190,251,25,91,11,23)
main :: IO ()
main = do
writeCodeGenModule "my_func.bc" g
-- I'd also like to use `g` in LLVM's JIT.
-- So, I'd like to pass `myVec` and 3 to `g`.
-- Initialize jitter
initializeNativeTarget
-- I get stuck here:
unwrappedIOf <- simpleFunction g
{-
No instance for (Generic (Vector D8 Float))
arising from a use of `simpleFunction'
-}
-- This is due to a lack of a Vector instance for Generic.
-- OK, but now I'm not sure how to do what I'd like to do:
-- I'd like apply float 3 and vector `myVec` to g in the JIT.
-- Then, I'd like to convert the vector returned by `g`.
-- There are no examples in the llvm github with how to use
-- the `toVector` and `fromVector`, or how to extract values
-- from vectors.
The text was updated successfully, but these errors were encountered:
To elaborate more: the "llvm-base" haskell binding is fragile, has a complex build system, and doesn't present a good Haskell style layer for the core api. LLVM-General is better by all of these metrics. Additionally, theres work in progress to have a strongly typed analogue of "llvm" on top of llvm-general https://github.com/alphaHeavy/llvm-general-typed
Hopefully the code below is self explanatory. Due to a lack on a Vector Generic instance, I cannot use
simpleFunction
ong
. I also cannot see how to usefromVector
.The text was updated successfully, but these errors were encountered: