crucible-llvm-0.6: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2018
LicenseBSD3
MaintainerRob Dockins <rdockins@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM.Ctors

Description

 
Synopsis

Documentation

data Ctor Source #

A representation of well-typed inhabitants of the llvm.global_ctors array

See https://llvm.org/docs/LangRef.html#the-llvm-global-ctors-global-variable

Instances

Instances details
Data Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

Methods

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

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

toConstr :: Ctor -> Constr #

dataTypeOf :: Ctor -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

Associated Types

type Rep Ctor :: Type -> Type #

Methods

from :: Ctor -> Rep Ctor x #

to :: Rep Ctor x -> Ctor #

Show Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

Methods

showsPrec :: Int -> Ctor -> ShowS #

show :: Ctor -> String #

showList :: [Ctor] -> ShowS #

Eq Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

Methods

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

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

Ord Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

Methods

compare :: Ctor -> Ctor -> Ordering #

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

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

(>) :: Ctor -> Ctor -> Bool #

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

max :: Ctor -> Ctor -> Ctor #

min :: Ctor -> Ctor -> Ctor #

type Rep Ctor Source # 
Instance details

Defined in Lang.Crucible.LLVM.Ctors

type Rep Ctor = D1 ('MetaData "Ctor" "Lang.Crucible.LLVM.Ctors" "crucible-llvm-0.6-JJ7tfvbGrbFFTkl5eJBN3H" 'False) (C1 ('MetaCons "Ctor" 'PrefixI 'True) (S1 ('MetaSel ('Just "ctorPriority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: (S1 ('MetaSel ('Just "ctorFunction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol) :*: S1 ('MetaSel ('Just "ctorData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Symbol)))))

globalCtors :: MonadError String m => Module -> m [Ctor] Source #

Unpack and sort the values in llvm.global_ctors by priority

callCtors Source #

Arguments

:: (Ctor -> Bool)

Filter function

-> Module 
-> LLVMGenerator s arch UnitType (Expr LLVM s UnitType) 

Call some or all of the functions in llvm.global_ctors

callAllCtors :: Module -> LLVMGenerator s arch UnitType (Expr LLVM s UnitType) Source #

Call each function in llvm.global_ctors in order of decreasing priority

callCtorsCFG Source #

Arguments

:: forall arch wptr. (HasPtrWidth wptr, wptr ~ ArchWidth arch, 16 <= wptr) 
=> (Ctor -> Bool)

Filter function

-> Module 
-> HandleAllocator 
-> LLVMContext arch 
-> IO (SomeCFG LLVM EmptyCtx UnitType) 

Create a CFG that calls some of the functions in llvm.global_ctors.