module LLVM.Extra.Extension (
T, Result, CallArgs,
Subtarget(Subtarget), wrap,
intrinsic, intrinsicAttr,
run, runWhen, runUnsafe,
with, with2, with3,
) where
import qualified LLVM.Core as LLVM
import LLVM.Core
(Value, CodeGenFunction, externFunction, call,
addAttributes, Attribute , )
import Data.Map (Map, )
import qualified Data.Map as Map
import Control.Monad.Trans.Writer (Writer, writer, runWriter, )
import Control.Monad (join, )
import Control.Applicative (Applicative, pure, (<*>), )
import Prelude hiding (replicate, sum, map, zipWith, )
data Subtarget =
Subtarget {
targetName, name :: String,
check :: forall r. CodeGenFunction r Bool
}
newtype T a =
Cons (Writer (Map String Subtarget) a)
deriving (Functor, Applicative)
wrap :: Subtarget -> a -> T a
wrap tar cgf =
Cons $
writer (cgf, Map.singleton (name tar) tar)
type family Result g :: *
type instance Result (a -> g) = Result g
type instance Result (CodeGenFunction r a) = r
class CallArgs g where
buildIntrinsic :: [Attribute] -> CodeGenFunction (Result g) g -> g
instance (CallArgs g) =>
CallArgs (Value a -> g) where
buildIntrinsic attrs g x =
buildIntrinsic attrs (fmap ($x) g)
instance CallArgs (CodeGenFunction r (Value a)) where
buildIntrinsic attrs g = do
z <- join g
addAttributes z 0 attrs
return z
intrinsic ::
(LLVM.IsFunction f, LLVM.CallArgs f g (Result g), CallArgs g) =>
Subtarget -> String -> T g
intrinsic =
intrinsicAttr []
intrinsicAttr ::
(LLVM.IsFunction f, LLVM.CallArgs f g (Result g), CallArgs g) =>
[Attribute] -> Subtarget -> String -> T g
intrinsicAttr attrs tar intr =
wrap tar $
buildIntrinsic attrs $
fmap call $
externFunction $
"llvm." ++ targetName tar ++ "." ++ name tar ++ "." ++ intr
infixl 1 `run`
run ::
CodeGenFunction r a ->
T (CodeGenFunction r a) ->
CodeGenFunction r a
run alt (Cons m) = do
let (a,s) = runWriter m
b <- mapM check (Map.elems s)
if and b
then a
else alt
runWhen ::
Bool ->
CodeGenFunction r a ->
T (CodeGenFunction r a) ->
CodeGenFunction r a
runWhen c alt (Cons m) = do
let (a,s) = runWriter m
b <- mapM check (Map.elems s)
if c && and b
then a
else alt
runUnsafe ::
T a -> a
runUnsafe (Cons m) =
fst $ runWriter m
with :: (Functor f) => f a -> (a -> b) -> f b
with = flip fmap
with2 :: (Applicative f) => f a -> f b -> (a -> b -> c) -> f c
with2 a b f =
pure f <*> a <*> b
with3 :: (Applicative f) => f a -> f b -> f c -> (a -> b -> c -> d) -> f d
with3 a b c f =
pure f <*> a <*> b <*> c