Safe Haskell | None |
---|
- data Literal
- mkMachInt :: Integer -> Literal
- mkMachWord :: Integer -> Literal
- mkMachInt64 :: Integer -> Literal
- mkMachWord64 :: Integer -> Literal
- mkMachFloat :: Rational -> Literal
- mkMachDouble :: Rational -> Literal
- mkMachChar :: Char -> Literal
- mkMachString :: String -> Literal
- mkLitInteger :: Integer -> Type -> Literal
- literalType :: Literal -> Type
- hashLiteral :: Literal -> Int
- absentLiteralOf :: TyCon -> Maybe Literal
- pprLiteral :: (SDoc -> SDoc) -> Literal -> SDoc
- litIsDupable :: Literal -> Bool
- litIsTrivial :: Literal -> Bool
- litIsLifted :: Literal -> Bool
- inIntRange :: Integer -> Bool
- inWordRange :: Integer -> Bool
- tARGET_MAX_INT :: Integer
- inCharRange :: Char -> Bool
- isZeroLit :: Literal -> Bool
- litFitsInChar :: Literal -> Bool
- word2IntLit :: Literal -> Literal
- int2WordLit :: Literal -> Literal
- narrow8IntLit :: Literal -> Literal
- narrow16IntLit :: Literal -> Literal
- narrow32IntLit :: Literal -> Literal
- narrow8WordLit :: Literal -> Literal
- narrow16WordLit :: Literal -> Literal
- narrow32WordLit :: Literal -> Literal
- char2IntLit :: Literal -> Literal
- int2CharLit :: Literal -> Literal
- float2IntLit :: Literal -> Literal
- int2FloatLit :: Literal -> Literal
- double2IntLit :: Literal -> Literal
- int2DoubleLit :: Literal -> Literal
- nullAddrLit :: Literal
- float2DoubleLit :: Literal -> Literal
- double2FloatLit :: Literal -> Literal
Main data type
So-called Literal
s are one of:
MachChar Char |
|
MachStr FastString | A string-literal: stored and emitted
UTF-8 encoded, we'll arrange to decode it
at runtime. Also emitted with a |
MachNullAddr | The |
MachInt Integer |
|
MachInt64 Integer |
|
MachWord Integer |
|
MachWord64 Integer |
|
MachFloat Rational |
|
MachDouble Rational |
|
MachLabel FastString (Maybe Int) FunctionOrData | A label literal. Parameters: 1) The name of the symbol mentioned in the declaration 2) The size (in bytes) of the arguments
the label expects. Only applicable with
|
LitInteger Integer Type |
Creating Literals
mkMachWord :: Integer -> LiteralSource
Creates a Literal
of type Word#
mkMachInt64 :: Integer -> LiteralSource
Creates a Literal
of type Int64#
mkMachWord64 :: Integer -> LiteralSource
Creates a Literal
of type Word64#
mkMachFloat :: Rational -> LiteralSource
Creates a Literal
of type Float#
mkMachDouble :: Rational -> LiteralSource
Creates a Literal
of type Double#
mkMachChar :: Char -> LiteralSource
Creates a Literal
of type Char#
mkMachString :: String -> LiteralSource
Creates a Literal
of type Addr#
, which is appropriate for passing to
e.g. some of the "error" functions in GHC.Err such as GHC.Err.runtimeError
mkLitInteger :: Integer -> Type -> LiteralSource
Operations on Literals
literalType :: Literal -> TypeSource
Find the Haskell Type
the literal occupies
hashLiteral :: Literal -> IntSource
Predicates on Literals and their contents
litIsDupable :: Literal -> BoolSource
True if code space does not go bad if we duplicate this literal
Currently we treat it just like litIsTrivial
litIsTrivial :: Literal -> BoolSource
True if there is absolutely no penalty to duplicating the literal. False principally of strings
litIsLifted :: Literal -> BoolSource
inIntRange :: Integer -> BoolSource
inWordRange :: Integer -> BoolSource
inCharRange :: Char -> BoolSource
isZeroLit :: Literal -> BoolSource
Tests whether the literal represents a zero of whatever type it is
litFitsInChar :: Literal -> BoolSource
Coercions
word2IntLit :: Literal -> LiteralSource
int2WordLit :: Literal -> LiteralSource
char2IntLit :: Literal -> LiteralSource
int2CharLit :: Literal -> LiteralSource
float2IntLit :: Literal -> LiteralSource
int2FloatLit :: Literal -> LiteralSource