llvm-hs-pure-4.0.0.0: Pure Haskell LLVM functionality (no FFI).

Safe HaskellSafe
LanguageHaskell98

LLVM.AST.Type

Description

A representation of an LLVM type

Synopsis

Documentation

data FloatingPointFormat Source #

LLVM supports some special formats floating point format. This type is to distinguish those format. I believe it's treated as a format for "a" float, as opposed to a vector of two floats, because its intended usage is to represent a single number with a combined significand.

Instances

Eq FloatingPointFormat Source # 
Data FloatingPointFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloatingPointFormat -> c FloatingPointFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloatingPointFormat #

toConstr :: FloatingPointFormat -> Constr #

dataTypeOf :: FloatingPointFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloatingPointFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloatingPointFormat) #

gmapT :: (forall b. Data b => b -> b) -> FloatingPointFormat -> FloatingPointFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloatingPointFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloatingPointFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloatingPointFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloatingPointFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloatingPointFormat -> m FloatingPointFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatingPointFormat -> m FloatingPointFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatingPointFormat -> m FloatingPointFormat #

Ord FloatingPointFormat Source # 
Read FloatingPointFormat Source # 
Show FloatingPointFormat Source # 

data Type Source #

Instances

Eq Type Source # 

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Data Type Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type #

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Type) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) #

gmapT :: (forall b. Data b => b -> b) -> Type -> Type #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r #

gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type #

Ord Type Source # 

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Read Type Source # 
Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

void :: Type Source #

An abbreviation for VoidType

i1 :: Type Source #

An abbreviation for IntegerType 1

i8 :: Type Source #

An abbreviation for IntegerType 8

i16 :: Type Source #

An abbreviation for IntegerType 16

i32 :: Type Source #

An abbreviation for IntegerType 32

i64 :: Type Source #

An abbreviation for IntegerType 64

i128 :: Type Source #

An abbreviation for IntegerType 128

ptr :: Type -> Type Source #

An abbreviation for PointerType t (AddrSpace 0)

half :: Type Source #

An abbreviation for FloatingPointType 16 IEEE

float :: Type Source #

An abbreviation for FloatingPointType 32 IEEE

double :: Type Source #

An abbreviation for FloatingPointType 64 IEEE

fp128 :: Type Source #

An abbreviation for FloatingPointType 128 IEEE