Skip to content

Instantly share code, notes, and snippets.

@smoge
Last active June 11, 2024 11:25
Show Gist options
  • Save smoge/289a50b533e94d42efc824b0cd97650f to your computer and use it in GitHub Desktop.
Save smoge/289a50b533e94d42efc824b0cd97650f to your computer and use it in GitHub Desktop.
llvm-gen-test.hs
{-
import("stdfaust.lib");
freq = hslider("freq", 440, 20, 20000, 0.01);
process = os.osc(freq) <: _, _;
faust -lang llvm sine_wave.dsp -o sine_wave.ll
-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.Process
import System.IO.Temp
import System.IO
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import Foreign.Ptr (FunPtr, castFunPtr, Ptr)
import LLVM.AST as AST
import LLVM.Context
import LLVM.Module
import LLVM.ExecutionEngine
generateLLVMIR :: String -> IO ByteString
generateLLVMIR faustCode = withSystemTempFile "temp.dsp" $ \dspPath dspHandle -> do
hPutStr dspHandle faustCode
hFlush dspHandle
let llPath = dspPath ++ ".ll"
callProcess "faust" ["-lang", "llvm", dspPath, "-o", llPath]
BS.readFile llPath
compileLLVMModule :: ByteString -> IO (FunPtr (Ptr Float -> Ptr Float -> IO ()))
compileLLVMModule llvmIR = withContext $ \context -> do
withModuleFromLLVMAssembly context llvmIR $ \m -> do
withExecutionEngine context $ \executionEngine -> do
withModuleInEngine executionEngine m $ \_ -> do
functionPtr <- getFunction executionEngine "process"
case functionPtr of
Just fn -> return (castFunPtr fn)
Nothing -> error "Function not found"
main :: IO ()
main = do
let faustCode = "import(\"stdfaust.lib\");\n" ++
"freq = hslider(\"freq\", 440, 20, 20000, 0.01);\n" ++
"process = os.osc(freq) <: _, _;\n"
llvmIR <- generateLLVMIR faustCode
functionPtr <- compileLLVMModule llvmIR
let processFunc = functionPtr :: Ptr Float -> Ptr Float -> IO ()
-- call processFunc with arguments for real-time audio
return ()
{-
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- process
- bytestring
- llvm-hs
- llvm-hs-pure
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment