ghc-9.4.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Literal

Description

Core literals

Synopsis

Main data type

data Literal Source #

So-called Literals are one of:

  • An unboxed numeric literal or floating-point literal which is presumed to be surrounded by appropriate constructors (Int#, etc.), so that the overall thing makes sense.

We maintain the invariant that the Integer in the LitNumber constructor is actually in the (possibly target-dependent) range. The mkLit{Int,Word}*Wrap smart constructors ensure this by applying the target machine's wrapping semantics. Use these in situations where you know the wrapping semantics are correct.

  • The literal derived from the label mentioned in a "foreign label" declaration (LitLabel)
  • A LitRubbish to be used in place of values that are never used.
  • A character
  • A string
  • The NULL pointer

Constructors

LitChar Char

Char# - at least 31 bits. Create with mkLitChar

LitNumber !LitNumType !Integer

Any numeric literal that can be internally represented with an Integer.

LitString !ByteString

A string-literal: stored and emitted UTF-8 encoded, we'll arrange to decode it at runtime. Also emitted with a '\0' terminator. Create with mkLitString

LitNullAddr

The NULL pointer, the only pointer value that can be represented as a Literal. Create with nullAddrLit

LitRubbish Type

A nonsense value of the given representation. See Note [Rubbish literals].

The Type argument, rr, is of kind RuntimeRep. The type of the literal is forall (a:TYPE rr). a

INVARIANT: the Type has no free variables and so substitution etc can ignore it

LitFloat Rational

Float#. Create with mkLitFloat

LitDouble Rational

Double#. Create with mkLitDouble

LitLabel 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 stdcall labels. Just x => <x> will be appended to label name when emitting assembly.

3) Flag indicating whether the symbol references a function or a data

Instances

Instances details
Data Literal Source # 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

toConstr :: Literal -> Constr Source #

dataTypeOf :: Literal -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary Literal Source # 
Instance details

Defined in GHC.Types.Literal

Outputable Literal Source # 
Instance details

Defined in GHC.Types.Literal

Methods

ppr :: Literal -> SDoc Source #

Eq Literal Source # 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

Ord Literal Source #

Needed for the Ord instance of AltCon, which in turn is needed in CoreMap.

Instance details

Defined in GHC.Types.Literal

data LitNumType Source #

Numeric literal type

Constructors

LitNumBigNat

Bignat (see Note [BigNum literals])

LitNumInt

Int# - according to target machine

LitNumInt8

Int8# - exactly 8 bits

LitNumInt16

Int16# - exactly 16 bits

LitNumInt32

Int32# - exactly 32 bits

LitNumInt64

Int64# - exactly 64 bits

LitNumWord

Word# - according to target machine

LitNumWord8

Word8# - exactly 8 bits

LitNumWord16

Word16# - exactly 16 bits

LitNumWord32

Word32# - exactly 32 bits

LitNumWord64

Word64# - exactly 64 bits

Instances

Instances details
Data LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

toConstr :: LitNumType -> Constr Source #

dataTypeOf :: LitNumType -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Enum LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Binary LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Eq LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Ord LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Creating Literals

mkLitInt :: Platform -> Integer -> Literal Source #

Creates a Literal of type Int#

mkLitIntWrap :: Platform -> Integer -> Literal Source #

Creates a Literal of type Int#. If the argument is out of the (target-dependent) range, it is wrapped. See Note [WordInt underflowoverflow]

mkLitIntWrapC :: Platform -> Integer -> (Literal, Bool) Source #

Creates a Literal of type Int#, as well as a Boolean flag indicating overflow. That is, if the argument is out of the (target-dependent) range the argument is wrapped and the overflow flag will be set. See Note [WordInt underflowoverflow]

mkLitIntUnchecked :: Integer -> Literal Source #

Creates a Literal of type Int# without checking its range.

mkLitWord :: Platform -> Integer -> Literal Source #

Creates a Literal of type Word#

mkLitWordWrap :: Platform -> Integer -> Literal Source #

Creates a Literal of type Word#. If the argument is out of the (target-dependent) range, it is wrapped. See Note [WordInt underflowoverflow]

mkLitWordWrapC :: Platform -> Integer -> (Literal, Bool) Source #

Creates a Literal of type Word#, as well as a Boolean flag indicating carry. That is, if the argument is out of the (target-dependent) range the argument is wrapped and the carry flag will be set. See Note [WordInt underflowoverflow]

mkLitWordUnchecked :: Integer -> Literal Source #

Creates a Literal of type Word# without checking its range.

mkLitInt8 :: Integer -> Literal Source #

Creates a Literal of type Int8#

mkLitInt8Wrap :: Integer -> Literal Source #

Creates a Literal of type Int8#. If the argument is out of the range, it is wrapped.

mkLitInt8Unchecked :: Integer -> Literal Source #

Creates a Literal of type Int8# without checking its range.

mkLitWord8 :: Integer -> Literal Source #

Creates a Literal of type Word8#

mkLitWord8Wrap :: Integer -> Literal Source #

Creates a Literal of type Word8#. If the argument is out of the range, it is wrapped.

mkLitWord8Unchecked :: Integer -> Literal Source #

Creates a Literal of type Word8# without checking its range.

mkLitInt16 :: Integer -> Literal Source #

Creates a Literal of type Int16#

mkLitInt16Wrap :: Integer -> Literal Source #

Creates a Literal of type Int16#. If the argument is out of the range, it is wrapped.

mkLitInt16Unchecked :: Integer -> Literal Source #

Creates a Literal of type Int16# without checking its range.

mkLitWord16 :: Integer -> Literal Source #

Creates a Literal of type Word16#

mkLitWord16Wrap :: Integer -> Literal Source #

Creates a Literal of type Word16#. If the argument is out of the range, it is wrapped.

mkLitWord16Unchecked :: Integer -> Literal Source #

Creates a Literal of type Word16# without checking its range.

mkLitInt32 :: Integer -> Literal Source #

Creates a Literal of type Int32#

mkLitInt32Wrap :: Integer -> Literal Source #

Creates a Literal of type Int32#. If the argument is out of the range, it is wrapped.

mkLitInt32Unchecked :: Integer -> Literal Source #

Creates a Literal of type Int32# without checking its range.

mkLitWord32 :: Integer -> Literal Source #

Creates a Literal of type Word32#

mkLitWord32Wrap :: Integer -> Literal Source #

Creates a Literal of type Word32#. If the argument is out of the range, it is wrapped.

mkLitWord32Unchecked :: Integer -> Literal Source #

Creates a Literal of type Word32# without checking its range.

mkLitInt64 :: Integer -> Literal Source #

Creates a Literal of type Int64#

mkLitInt64Wrap :: Integer -> Literal Source #

Creates a Literal of type Int64#. If the argument is out of the range, it is wrapped.

mkLitInt64Unchecked :: Integer -> Literal Source #

Creates a Literal of type Int64# without checking its range.

mkLitWord64 :: Integer -> Literal Source #

Creates a Literal of type Word64#

mkLitWord64Wrap :: Integer -> Literal Source #

Creates a Literal of type Word64#. If the argument is out of the range, it is wrapped.

mkLitWord64Unchecked :: Integer -> Literal Source #

Creates a Literal of type Word64# without checking its range.

mkLitFloat :: Rational -> Literal Source #

Creates a Literal of type Float#

mkLitDouble :: Rational -> Literal Source #

Creates a Literal of type Double#

mkLitChar :: Char -> Literal Source #

Creates a Literal of type Char#

mkLitString :: String -> Literal Source #

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

mkLitNumber :: Platform -> LitNumType -> Integer -> Literal Source #

Create a numeric Literal of the given type

mkLitNumberWrap :: Platform -> LitNumType -> Integer -> Literal Source #

Make a literal number using wrapping semantics if the value is out of bound.

Operations on Literals

literalType :: Literal -> Type Source #

Find the Haskell Type the literal occupies

litNumIsSigned :: LitNumType -> Bool Source #

Indicate if a numeric literal type supports negative numbers

litNumRange :: Platform -> LitNumType -> (Maybe Integer, Maybe Integer) Source #

Get the literal range

litNumCheckRange :: Platform -> LitNumType -> Integer -> Bool Source #

Check that a given number is in the range of a numeric literal

litNumWrap :: Platform -> Literal -> Literal Source #

Wrap a literal number according to its type using wrapping semantics.

litNumCoerce :: LitNumType -> Platform -> Literal -> Literal Source #

Coerce a literal number into another using wrapping semantics.

litNumNarrow :: LitNumType -> Platform -> Literal -> Literal Source #

Narrow a literal number by converting it into another number type and then converting it back to its original type.

Predicates on Literals and their contents

litIsDupable :: Platform -> Literal -> Bool Source #

True if code space does not go bad if we duplicate this literal

litIsTrivial :: Literal -> Bool Source #

True if there is absolutely no penalty to duplicating the literal. False principally of strings.

"Why?", you say? I'm glad you asked. Well, for one duplicating strings would blow up code sizes. Not only this, it's also unsafe.

Consider a program that wants to traverse a string. One way it might do this is to first compute the Addr# pointing to the end of the string, and then, starting from the beginning, bump a pointer using eqAddr# to determine the end. For instance,

-- Given pointers to the start and end of a string, count how many zeros
-- the string contains.
countZeros :: Addr# -> Addr# -> -> Int
countZeros start end = go start 0
  where
    go off n
      | off addrEq# end = n
      | otherwise         = go (off plusAddr# 1) n'
      where n' | isTrue# (indexInt8OffAddr# off 0# ==# 0#) = n + 1
               | otherwise                                 = n

Consider what happens if we considered strings to be trivial (and therefore duplicable) and emitted a call like countZeros "hello"# ("hello"# plusAddr# 5). The beginning and end pointers do not belong to the same string, meaning that an iteration like the above would blow up terribly. This is what happened in #12757.

Ultimately the solution here is to make primitive strings a bit more structured, ensuring that the compiler can't inline in ways that will break user code. One approach to this is described in #8472.

isZeroLit :: Literal -> Bool Source #

Tests whether the literal represents a zero of whatever type it is

isOneLit :: Literal -> Bool Source #

Tests whether the literal represents a one of whatever type it is

litValue :: Literal -> Integer Source #

Returns the Integer contained in the Literal, for when that makes sense, i.e. for Char and numbers.

mapLitValue :: Platform -> (Integer -> Integer) -> Literal -> Literal Source #

Apply a function to the Integer contained in the Literal, for when that makes sense, e.g. for Char and numbers. For fixed-size integral literals, the result will be wrapped in accordance with the semantics of the target type. See Note [WordInt underflowoverflow]

isLitValue_maybe :: Literal -> Maybe Integer Source #

Returns the Integer contained in the Literal, for when that makes sense, i.e. for Char and numbers.

Coercions

convertToIntLit :: Platform -> Literal -> Literal Source #

Extend or narrow a fixed-width literal (e.g. Int16#) to a target word-sized literal (Int# or Word#). Narrowing can only happen on 32-bit architectures when we convert a 64-bit literal into a 32-bit one.

convertToWordLit :: Platform -> Literal -> Literal Source #

Extend or narrow a fixed-width literal (e.g. Int16#) to a target word-sized literal (Int# or Word#). Narrowing can only happen on 32-bit architectures when we convert a 64-bit literal into a 32-bit one.