llvm-pretty-0.7.1.0: A pretty printing library inspired by the llvm binding.

Safe HaskellSafe
LanguageHaskell2010

Text.LLVM.Labels

Synopsis

Documentation

genericRelabel :: (Applicative m, Generic1 f, GHasLabel (Rep1 f)) => (Maybe Symbol -> a -> m b) -> f a -> m (f b) Source #

Generic implementation of relabel the never provides symbols

class GHasLabel f where Source #

Implementation details for genericRelabel

Minimal complete definition

grelabel

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> f a -> m (f b) Source #

Instances

GHasLabel V1 Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> V1 a -> m (V1 b) Source #

GHasLabel U1 Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> U1 a -> m (U1 b) Source #

GHasLabel Par1 Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Par1 a -> m (Par1 b) Source #

HasLabel f => GHasLabel (Rec1 f) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Rec1 f a -> m (Rec1 f b) Source #

GHasLabel (K1 i a) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> K1 i a a -> m (K1 i a b) Source #

(GHasLabel f, GHasLabel g) => GHasLabel ((:+:) f g) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source #

(GHasLabel f, GHasLabel g) => GHasLabel ((:*:) f g) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source #

(Traversable f, GHasLabel g) => GHasLabel ((:.:) f g) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source #

GHasLabel f => GHasLabel (M1 i c f) Source # 

Methods

grelabel :: Applicative m => (Maybe Symbol -> a -> m b) -> M1 i c f a -> m (M1 i c f b) Source #

class Functor f => HasLabel f where Source #

Minimal complete definition

relabel

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> f a -> m (f b) Source #

Given a function for resolving labels, where the presence of a symbol denotes a label in a different function, rename all labels in a function.

Instances

HasLabel DISubroutineType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DISubroutineType' a -> m (DISubroutineType' b) Source #

HasLabel DISubprogram' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DISubprogram' a -> m (DISubprogram' b) Source #

HasLabel DILocalVariable' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILocalVariable' a -> m (DILocalVariable' b) Source #

HasLabel DILexicalBlockFile' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILexicalBlockFile' a -> m (DILexicalBlockFile' b) Source #

HasLabel DILexicalBlock' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILexicalBlock' a -> m (DILexicalBlock' b) Source #

HasLabel DIGlobalVariableExpression' Source # 
HasLabel DIGlobalVariable' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DIGlobalVariable' a -> m (DIGlobalVariable' b) Source #

HasLabel DIDerivedType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DIDerivedType' a -> m (DIDerivedType' b) Source #

HasLabel DICompositeType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DICompositeType' a -> m (DICompositeType' b) Source #

HasLabel DICompileUnit' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DICompileUnit' a -> m (DICompileUnit' b) Source #

HasLabel DebugInfo' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DebugInfo' a -> m (DebugInfo' b) Source #

HasLabel ConstExpr' Source #

Clever instance that actually uses the block name

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> ConstExpr' a -> m (ConstExpr' b) Source #

HasLabel Stmt' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Stmt' a -> m (Stmt' b) Source #

HasLabel DebugLoc' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DebugLoc' a -> m (DebugLoc' b) Source #

HasLabel ValMd' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> ValMd' a -> m (ValMd' b) Source #

HasLabel Value' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Value' a -> m (Value' b) Source #

HasLabel Clause' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Clause' a -> m (Clause' b) Source #

HasLabel Instr' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Instr' a -> m (Instr' b) Source #