module LLVM.IRBuilder.Constant where import Data.Word import LLVM.Prelude import LLVM.AST hiding (args, dests) import LLVM.AST.Typed import LLVM.AST.Constant import LLVM.AST.Float import LLVM.IRBuilder.Module import GHC.Stack int64 :: Integer -> Operand int64 :: Integer -> Operand int64 = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Integer -> Constant) -> Integer -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . Word32 -> Integer -> Constant Int Word32 64 int32 :: Integer -> Operand int32 :: Integer -> Operand int32 = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Integer -> Constant) -> Integer -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . Word32 -> Integer -> Constant Int Word32 32 int16 :: Integer -> Operand int16 :: Integer -> Operand int16 = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Integer -> Constant) -> Integer -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . Word32 -> Integer -> Constant Int Word32 16 int8 :: Integer -> Operand int8 :: Integer -> Operand int8 = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Integer -> Constant) -> Integer -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . Word32 -> Integer -> Constant Int Word32 8 bit :: Integer -> Operand bit :: Integer -> Operand bit = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Integer -> Constant) -> Integer -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . Word32 -> Integer -> Constant Int Word32 1 double :: Double -> Operand double :: Double -> Operand double = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Double -> Constant) -> Double -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . SomeFloat -> Constant Float (SomeFloat -> Constant) -> (Double -> SomeFloat) -> Double -> Constant forall b c a. (b -> c) -> (a -> b) -> a -> c . Double -> SomeFloat Double single :: Float -> Operand single :: Float -> Operand single = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Float -> Constant) -> Float -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . SomeFloat -> Constant Float (SomeFloat -> Constant) -> (Float -> SomeFloat) -> Float -> Constant forall b c a. (b -> c) -> (a -> b) -> a -> c . Float -> SomeFloat Single half :: Word16 -> Operand half :: Word16 -> Operand half = Constant -> Operand ConstantOperand (Constant -> Operand) -> (Word16 -> Constant) -> Word16 -> Operand forall b c a. (b -> c) -> (a -> b) -> a -> c . SomeFloat -> Constant Float (SomeFloat -> Constant) -> (Word16 -> SomeFloat) -> Word16 -> Constant forall b c a. (b -> c) -> (a -> b) -> a -> c . Word16 -> SomeFloat Half struct :: Maybe Name -> Bool -> [Constant] -> Operand struct :: Maybe Name -> Bool -> [Constant] -> Operand struct Maybe Name nm Bool packing [Constant] members = Constant -> Operand ConstantOperand (Constant -> Operand) -> Constant -> Operand forall a b. (a -> b) -> a -> b $ Maybe Name -> Bool -> [Constant] -> Constant Struct Maybe Name nm Bool packing [Constant] members array :: (HasCallStack, MonadModuleBuilder m) => [Constant] -> m Operand array :: forall (m :: * -> *). (HasCallStack, MonadModuleBuilder m) => [Constant] -> m Operand array [Constant] members = do Either String Type thm <- Constant -> m (Either String Type) forall a (m :: * -> *). (Typed a, HasCallStack, MonadModuleBuilder m) => a -> m (Either String Type) forall (m :: * -> *). (HasCallStack, MonadModuleBuilder m) => Constant -> m (Either String Type) typeOf (Constant -> m (Either String Type)) -> Constant -> m (Either String Type) forall a b. (a -> b) -> a -> b $ [Constant] -> Constant forall a. HasCallStack => [a] -> a head [Constant] members case Either String Type thm of (Left String s) -> String -> m Operand forall a. HasCallStack => String -> a error String s (Right Type thm') -> Operand -> m Operand forall a. a -> m a forall (m :: * -> *) a. Monad m => a -> m a return (Operand -> m Operand) -> Operand -> m Operand forall a b. (a -> b) -> a -> b $ Constant -> Operand ConstantOperand (Constant -> Operand) -> Constant -> Operand forall a b. (a -> b) -> a -> b $ Type -> [Constant] -> Constant Array Type thm' [Constant] members