llvm-party-12.1.1: General purpose LLVM bindings
Safe HaskellSafe-Inferred
LanguageHaskell2010

LLVM.AST.Name

Description

Names as used in LLVM IR

Synopsis

Documentation

data Name Source #

Objects of various sorts in LLVM IR are identified by address in the LLVM C++ API, and may be given a string name. When printed to (resp. read from) human-readable LLVM assembly, objects without string names are numbered sequentially (resp. must be numbered sequentially). String names may be quoted, and are quoted when printed if they would otherwise be misread - e.g. when containing special characters.

7

means the seventh unnamed object, while

"7"

means the object named with the string "7".

This libraries handling of UnNames during translation of the AST down into C++ IR is somewhat more forgiving than the LLVM assembly parser: it does not require that unnamed values be numbered sequentially; however, the numbers of UnNames passed into C++ cannot be preserved in the C++ objects. If the C++ IR is printed as assembly or translated into a Haskell AST, unnamed nodes will be renumbered sequentially. Thus unnamed node numbers should be thought of as having any scope limited to the Module in which they are used.

Constructors

Name ShortByteString

a string name

UnName Word

a number for a nameless thing

Instances

Instances details
Data Name Source # 
Instance details

Defined in LLVM.AST.Name

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Name Source #

Using fromString on non-ASCII strings will throw an error.

Instance details

Defined in LLVM.AST.Name

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in LLVM.AST.Name

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Read Name Source # 
Instance details

Defined in LLVM.AST.Name

Show Name Source # 
Instance details

Defined in LLVM.AST.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in LLVM.AST.Name

Methods

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

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

Ord Name Source # 
Instance details

Defined in LLVM.AST.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

MonadAnyCont IO m => EncodeM m Name CString Source # 
Instance details

Defined in LLVM.Internal.EncodeAST

Methods

encodeM :: Name -> m CString Source #

DecodeM DecodeAST Name (Ptr BasicBlock) Source # 
Instance details

Defined in LLVM.Internal.DecodeAST

EncodeM EncodeAST Name (Ptr BasicBlock) Source # 
Instance details

Defined in LLVM.Internal.EncodeAST

type Rep Name Source # 
Instance details

Defined in LLVM.AST.Name

mkName :: String -> Name Source #

Create a Name based on an ASCII String. Non-ASCII strings will throw an error.