-- | A representation of an LLVM type
module LLVM.AST.Type where

import LLVM.Prelude

import LLVM.AST.AddrSpace
import LLVM.AST.Name

-- | LLVM supports some special formats floating point format. This type is to distinguish those format. Also see  <http://llvm.org/docs/LangRef.html#floating-point-types>
data FloatingPointType
  = HalfFP      -- ^ 16-bit floating point value
  | FloatFP     -- ^ 32-bit floating point value
  | DoubleFP    -- ^ 64-bit floating point value
  | FP128FP     -- ^ 128-bit floating point value (112-bit mantissa)
  | X86_FP80FP  -- ^ 80-bit floating point value (X87)
  | PPC_FP128FP -- ^ 128-bit floating point value (two 64-bits)
  deriving (FloatingPointType -> FloatingPointType -> Bool
(FloatingPointType -> FloatingPointType -> Bool)
-> (FloatingPointType -> FloatingPointType -> Bool)
-> Eq FloatingPointType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatingPointType -> FloatingPointType -> Bool
$c/= :: FloatingPointType -> FloatingPointType -> Bool
== :: FloatingPointType -> FloatingPointType -> Bool
$c== :: FloatingPointType -> FloatingPointType -> Bool
Eq, Eq FloatingPointType
Eq FloatingPointType =>
(FloatingPointType -> FloatingPointType -> Ordering)
-> (FloatingPointType -> FloatingPointType -> Bool)
-> (FloatingPointType -> FloatingPointType -> Bool)
-> (FloatingPointType -> FloatingPointType -> Bool)
-> (FloatingPointType -> FloatingPointType -> Bool)
-> (FloatingPointType -> FloatingPointType -> FloatingPointType)
-> (FloatingPointType -> FloatingPointType -> FloatingPointType)
-> Ord FloatingPointType
FloatingPointType -> FloatingPointType -> Bool
FloatingPointType -> FloatingPointType -> Ordering
FloatingPointType -> FloatingPointType -> FloatingPointType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FloatingPointType -> FloatingPointType -> FloatingPointType
$cmin :: FloatingPointType -> FloatingPointType -> FloatingPointType
max :: FloatingPointType -> FloatingPointType -> FloatingPointType
$cmax :: FloatingPointType -> FloatingPointType -> FloatingPointType
>= :: FloatingPointType -> FloatingPointType -> Bool
$c>= :: FloatingPointType -> FloatingPointType -> Bool
> :: FloatingPointType -> FloatingPointType -> Bool
$c> :: FloatingPointType -> FloatingPointType -> Bool
<= :: FloatingPointType -> FloatingPointType -> Bool
$c<= :: FloatingPointType -> FloatingPointType -> Bool
< :: FloatingPointType -> FloatingPointType -> Bool
$c< :: FloatingPointType -> FloatingPointType -> Bool
compare :: FloatingPointType -> FloatingPointType -> Ordering
$ccompare :: FloatingPointType -> FloatingPointType -> Ordering
$cp1Ord :: Eq FloatingPointType
Ord, ReadPrec [FloatingPointType]
ReadPrec FloatingPointType
Int -> ReadS FloatingPointType
ReadS [FloatingPointType]
(Int -> ReadS FloatingPointType)
-> ReadS [FloatingPointType]
-> ReadPrec FloatingPointType
-> ReadPrec [FloatingPointType]
-> Read FloatingPointType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FloatingPointType]
$creadListPrec :: ReadPrec [FloatingPointType]
readPrec :: ReadPrec FloatingPointType
$creadPrec :: ReadPrec FloatingPointType
readList :: ReadS [FloatingPointType]
$creadList :: ReadS [FloatingPointType]
readsPrec :: Int -> ReadS FloatingPointType
$creadsPrec :: Int -> ReadS FloatingPointType
Read, Int -> FloatingPointType -> ShowS
[FloatingPointType] -> ShowS
FloatingPointType -> String
(Int -> FloatingPointType -> ShowS)
-> (FloatingPointType -> String)
-> ([FloatingPointType] -> ShowS)
-> Show FloatingPointType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FloatingPointType] -> ShowS
$cshowList :: [FloatingPointType] -> ShowS
show :: FloatingPointType -> String
$cshow :: FloatingPointType -> String
showsPrec :: Int -> FloatingPointType -> ShowS
$cshowsPrec :: Int -> FloatingPointType -> ShowS
Show, Typeable, Typeable FloatingPointType
DataType
Constr
Typeable FloatingPointType =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> FloatingPointType
 -> c FloatingPointType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FloatingPointType)
-> (FloatingPointType -> Constr)
-> (FloatingPointType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FloatingPointType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FloatingPointType))
-> ((forall b. Data b => b -> b)
    -> FloatingPointType -> FloatingPointType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> FloatingPointType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FloatingPointType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> FloatingPointType -> m FloatingPointType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> FloatingPointType -> m FloatingPointType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> FloatingPointType -> m FloatingPointType)
-> Data FloatingPointType
FloatingPointType -> DataType
FloatingPointType -> Constr
(forall b. Data b => b -> b)
-> FloatingPointType -> FloatingPointType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FloatingPointType -> c FloatingPointType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FloatingPointType
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FloatingPointType -> u
forall u. (forall d. Data d => d -> u) -> FloatingPointType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FloatingPointType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FloatingPointType -> c FloatingPointType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FloatingPointType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FloatingPointType)
$cPPC_FP128FP :: Constr
$cX86_FP80FP :: Constr
$cFP128FP :: Constr
$cDoubleFP :: Constr
$cFloatFP :: Constr
$cHalfFP :: Constr
$tFloatingPointType :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
gmapMp :: (forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
gmapM :: (forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FloatingPointType -> m FloatingPointType
gmapQi :: Int -> (forall d. Data d => d -> u) -> FloatingPointType -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FloatingPointType -> u
gmapQ :: (forall d. Data d => d -> u) -> FloatingPointType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FloatingPointType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FloatingPointType -> r
gmapT :: (forall b. Data b => b -> b)
-> FloatingPointType -> FloatingPointType
$cgmapT :: (forall b. Data b => b -> b)
-> FloatingPointType -> FloatingPointType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FloatingPointType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FloatingPointType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FloatingPointType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FloatingPointType)
dataTypeOf :: FloatingPointType -> DataType
$cdataTypeOf :: FloatingPointType -> DataType
toConstr :: FloatingPointType -> Constr
$ctoConstr :: FloatingPointType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FloatingPointType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FloatingPointType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FloatingPointType -> c FloatingPointType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FloatingPointType -> c FloatingPointType
$cp1Data :: Typeable FloatingPointType
Data, (forall x. FloatingPointType -> Rep FloatingPointType x)
-> (forall x. Rep FloatingPointType x -> FloatingPointType)
-> Generic FloatingPointType
forall x. Rep FloatingPointType x -> FloatingPointType
forall x. FloatingPointType -> Rep FloatingPointType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FloatingPointType x -> FloatingPointType
$cfrom :: forall x. FloatingPointType -> Rep FloatingPointType x
Generic)

-- | <http://llvm.org/docs/LangRef.html#type-system>
data Type
  -- | <http://llvm.org/docs/LangRef.html#void-type>
  = VoidType
  -- | <http://llvm.org/docs/LangRef.html#integer-type>
  | IntegerType { Type -> Word32
typeBits :: Word32 }
  -- | <http://llvm.org/docs/LangRef.html#pointer-type>
  | PointerType { Type -> Type
pointerReferent :: Type, Type -> AddrSpace
pointerAddrSpace :: AddrSpace }
  -- | <http://llvm.org/docs/LangRef.html#floating-point-types>
  | FloatingPointType { Type -> FloatingPointType
floatingPointType :: FloatingPointType }
  -- | <http://llvm.org/docs/LangRef.html#function-type>
  | FunctionType { Type -> Type
resultType :: Type, Type -> [Type]
argumentTypes :: [Type], Type -> Bool
isVarArg :: Bool }
  -- | <http://llvm.org/docs/LangRef.html#vector-type>
  | VectorType { Type -> Word32
nVectorElements :: Word32, Type -> Type
elementType :: Type }
  -- | <http://llvm.org/docs/LangRef.html#structure-type>
  | StructureType { Type -> Bool
isPacked :: Bool, Type -> [Type]
elementTypes :: [Type] }
  -- | <http://llvm.org/docs/LangRef.html#array-type>
  | ArrayType { Type -> Word64
nArrayElements :: Word64, elementType :: Type }
  -- | <http://llvm.org/docs/LangRef.html#opaque-structure-types>
  | NamedTypeReference Name
  -- | <http://llvm.org/docs/LangRef.html#metadata-type>
  | MetadataType -- only to be used as a parameter type for a few intrinsics
  -- | <http://llvm.org/docs/LangRef.html#label-type>
  | LabelType -- only to be used as the type of block names
  -- | <http://llvm.org/docs/LangRef.html#token-type>
  | TokenType
  deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
$cp1Ord :: Eq Type
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Type]
$creadListPrec :: ReadPrec [Type]
readPrec :: ReadPrec Type
$creadPrec :: ReadPrec Type
readList :: ReadS [Type]
$creadList :: ReadS [Type]
readsPrec :: Int -> ReadS Type
$creadsPrec :: Int -> ReadS Type
Read, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type] -> ShowS
$cshowList :: [Type] -> ShowS
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> ShowS
$cshowsPrec :: Int -> Type -> ShowS
Show, Typeable, Typeable Type
DataType
Constr
Typeable Type =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Type -> c Type)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Type)
-> (Type -> Constr)
-> (Type -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Type))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type))
-> ((forall b. Data b => b -> b) -> Type -> Type)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r)
-> (forall u. (forall d. Data d => d -> u) -> Type -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Type -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Type -> m Type)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Type -> m Type)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Type -> m Type)
-> Data Type
Type -> DataType
Type -> Constr
(forall b. Data b => b -> b) -> Type -> Type
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
forall u. (forall d. Data d => d -> u) -> Type -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Type -> m Type
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Type)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
$cTokenType :: Constr
$cLabelType :: Constr
$cMetadataType :: Constr
$cNamedTypeReference :: Constr
$cArrayType :: Constr
$cStructureType :: Constr
$cVectorType :: Constr
$cFunctionType :: Constr
$cFloatingPointType :: Constr
$cPointerType :: Constr
$cIntegerType :: Constr
$cVoidType :: Constr
$tType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapMp :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapM :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
gmapQ :: (forall d. Data d => d -> u) -> Type -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Type -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
gmapT :: (forall b. Data b => b -> b) -> Type -> Type
$cgmapT :: (forall b. Data b => b -> b) -> Type -> Type
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Type)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Type)
dataTypeOf :: Type -> DataType
$cdataTypeOf :: Type -> DataType
toConstr :: Type -> Constr
$ctoConstr :: Type -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
$cp1Data :: Typeable Type
Data, (forall x. Type -> Rep Type x)
-> (forall x. Rep Type x -> Type) -> Generic Type
forall x. Rep Type x -> Type
forall x. Type -> Rep Type x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Type x -> Type
$cfrom :: forall x. Type -> Rep Type x
Generic)

-- | An abbreviation for 'VoidType'
void :: Type
void :: Type
void = Type
VoidType

-- | An abbreviation for 'IntegerType' 1
i1 :: Type
i1 :: Type
i1 = Word32 -> Type
IntegerType 1

-- | An abbreviation for 'IntegerType' 8
i8 :: Type
i8 :: Type
i8 = Word32 -> Type
IntegerType 8

-- | An abbreviation for 'IntegerType' 16
i16 :: Type
i16 :: Type
i16 = Word32 -> Type
IntegerType 16

-- | An abbreviation for 'IntegerType' 32
i32 :: Type
i32 :: Type
i32 = Word32 -> Type
IntegerType 32

-- | An abbreviation for 'IntegerType' 64
i64 :: Type
i64 :: Type
i64 = Word32 -> Type
IntegerType 64

-- | An abbreviation for 'IntegerType' 128
i128 :: Type
i128 :: Type
i128 = Word32 -> Type
IntegerType 128

-- | An abbreviation for 'PointerType' t ('AddrSpace' 0)
ptr :: Type -> Type
ptr :: Type -> Type
ptr t :: Type
t = Type -> AddrSpace -> Type
PointerType Type
t (Word32 -> AddrSpace
AddrSpace 0)

-- | An abbreviation for 'FloatingPointType' 'HalfFP'
half :: Type
half :: Type
half = FloatingPointType -> Type
FloatingPointType FloatingPointType
HalfFP

-- | An abbreviation for 'FloatingPointType' 'FloatFP'
float :: Type
float :: Type
float = FloatingPointType -> Type
FloatingPointType FloatingPointType
FloatFP

-- | An abbreviation for 'FloatingPointType' 'DoubleFP'
double :: Type
double :: Type
double = FloatingPointType -> Type
FloatingPointType FloatingPointType
DoubleFP

-- | An abbreviation for 'FloatingPointType' 'FP128FP'
fp128 :: Type
fp128 :: Type
fp128 = FloatingPointType -> Type
FloatingPointType FloatingPointType
FP128FP

-- | An abbreviation for 'FloatingPointType' 'X86_FP80FP'
x86_fp80 :: Type
x86_fp80 :: Type
x86_fp80 = FloatingPointType -> Type
FloatingPointType FloatingPointType
X86_FP80FP

-- | An abbreviation for 'FloatingPointType' 'PPC_FP128FP'
ppc_fp128 :: Type
ppc_fp128 :: Type
ppc_fp128 = FloatingPointType -> Type
FloatingPointType FloatingPointType
PPC_FP128FP