-- | A representation of an LLVM type module LLVM.General.AST.Type where import LLVM.General.AST.AddrSpace import LLVM.General.AST.Name import Data.Word (Word32, Word64) -- | 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. data FloatingPointFormat = IEEE | DoubleExtended | PairOfFloats deriving (Eq, Ord, Read, Show) -- | data Type -- | = VoidType -- | | IntegerType { typeBits :: Word32 } -- | | PointerType { pointerReferent :: Type, pointerAddrSpace :: AddrSpace } -- | | FloatingPointType { typeBits :: Word32, floatingPointFormat :: FloatingPointFormat } -- | | FunctionType { resultType :: Type, argumentTypes :: [Type], isVarArg :: Bool } -- | | VectorType { nVectorElements :: Word32, elementType :: Type } -- | | StructureType { isPacked :: Bool, elementTypes :: [Type] } -- | | ArrayType { nArrayElements :: Word64, elementType :: Type } -- | | NamedTypeReference Name -- | | MetadataType -- only to be used as a parameter type for a few intrinsics deriving (Eq, Ord, Read, Show)