ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Literal

Contents

Synopsis

Main data type

data Literal #

So-called Literals are one of:

  • An unboxed (machine) literal (MachInt, MachFloat, etc.), which is presumed to be surrounded by appropriate constructors (Int#, etc.), so that the overall thing makes sense.
  • The literal derived from the label mentioned in a "foreign label" declaration (MachLabel)

Constructors

MachChar Char

Char# - at least 31 bits. Create with mkMachChar

MachStr 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 mkMachString

MachNullAddr

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

MachInt Integer

Int# - at least WORD_SIZE_IN_BITS bits. Create with mkMachInt

MachInt64 Integer

Int64# - at least 64 bits. Create with mkMachInt64

MachWord Integer

Word# - at least WORD_SIZE_IN_BITS bits. Create with mkMachWord

MachWord64 Integer

Word64# - at least 64 bits. Create with mkMachWord64

MachFloat Rational

Float#. Create with mkMachFloat

MachDouble Rational

Double#. Create with mkMachDouble

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

LitInteger Integer Type 

Instances

Eq Literal # 

Methods

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

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

Data 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 :: (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 #

Ord Literal # 
Outputable Literal # 

Methods

ppr :: Literal -> SDoc #

pprPrec :: Rational -> Literal -> SDoc #

Binary Literal # 

Creating Literals

mkMachInt :: DynFlags -> Integer -> Literal #

Creates a Literal of type Int#

mkMachWord :: DynFlags -> Integer -> Literal #

Creates a Literal of type Word#

mkMachInt64 :: Integer -> Literal #

Creates a Literal of type Int64#

mkMachWord64 :: Integer -> Literal #

Creates a Literal of type Word64#

mkMachFloat :: Rational -> Literal #

Creates a Literal of type Float#

mkMachDouble :: Rational -> Literal #

Creates a Literal of type Double#

mkMachChar :: Char -> Literal #

Creates a Literal of type Char#

mkMachString :: String -> Literal #

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

Operations on Literals

literalType :: Literal -> Type #

Find the Haskell Type the literal occupies

Predicates on Literals and their contents

litIsDupable :: DynFlags -> Literal -> Bool #

True if code space does not go bad if we duplicate this literal Currently we treat it just like litIsTrivial

litIsTrivial :: Literal -> Bool #

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 -> -> Int
countZeros start end = go start 0
  where
    go off n
      | off `addrEq#` end = n
      | otherwise         = go (off `plusAddr#` 1) n'
      where n' | isTrue 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" 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 #

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

litValue :: Literal -> Integer #

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

Coercions