module Feldspar.Compiler.CallConv
( rewriteType
, buildHaskellType
, buildCType
)
where
import Language.Haskell.TH
import System.Plugins.MultiStage
import Foreign.Ptr (Ptr)
import Feldspar (Syntactic(..))
rewriteType :: Type -> Q Type
rewriteType t = applyTF ''Internal t >>= expandTF
haskellCC :: CallConv
haskellCC = CallConv { arg = return
, res = appT (conT ''IO) . return
}
feldsparCC :: CallConv
feldsparCC = CallConv { arg = ref . rep . return
, res = toIO . appT (conT ''Ptr) . rep . return
}
where
ref = appT (conT ''Ref)
rep = appT (conT ''Rep)
toIO t = appT (appT arrowT t) (appT (conT ''IO) (tupleT 0))
buildHaskellType :: Type -> Q Type
buildHaskellType = buildType haskellCC
buildCType :: Type -> Q Type
buildCType = buildType feldsparCC