{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} module LLVM.DSL.Expression.Maybe ( T(Cons), select, ) where import qualified LLVM.DSL.Expression as Expr import LLVM.DSL.Expression (Exp) import qualified LLVM.Extra.Multi.Value as MultiValue import qualified LLVM.Extra.Maybe as Maybe import qualified LLVM.Core as LLVM import qualified Control.Monad.HT as Monad data T a = Cons (Exp Bool) a {- | counterpart to 'Data.Maybe.fromMaybe' with swapped arguments -} select :: (MultiValue.Select a) => T (Exp a) -> Exp a -> Exp a select (Cons b a) d = Expr.select b a d instance (Expr.Aggregate exp mv) => Expr.Aggregate (T exp) (Maybe.T mv) where type MultiValuesOf (T exp) = Maybe.T (Expr.MultiValuesOf exp) type ExpressionsOf (Maybe.T mv) = T (Expr.ExpressionsOf mv) bundle (Cons b a) = Monad.lift2 Maybe.Cons (fmap unbool $ Expr.bundle b) (Expr.bundle a) dissect (Maybe.Cons b a) = Cons (Expr.dissect (MultiValue.Cons b)) (Expr.dissect a) unbool :: MultiValue.T Bool -> LLVM.Value Bool unbool (MultiValue.Cons b) = b