Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Haskell.Tools.AST.Ann
Description
Parts of AST representation for keeping extra data
- data RangeStage
- data NormRangeStage
- data RngTemplateStage
- data SrcTemplateStage
- data Dom name
- data IdDom
- type SemanticInfo (domain :: *) (node :: * -> * -> *) = SemanticInfo' domain (SemaInfoClassify node)
- data SameInfoNameCls
- data SameInfoExprCls
- data SameInfoImportCls
- data SameInfoModuleCls
- data SameInfoDefaultCls
- data SameInfoWildcardCls
- type family SemaInfoClassify (node :: * -> * -> *) where ...
- type family SemanticInfo' (domain :: *) (nodecls :: *)
- type Domain d = (Typeable d, Data d, SemanticInfo' d SameInfoDefaultCls ~ NoSemanticInfo, Data (SemanticInfo' d SameInfoNameCls), Data (SemanticInfo' d SameInfoExprCls), Data (SemanticInfo' d SameInfoImportCls), Data (SemanticInfo' d SameInfoModuleCls), Data (SemanticInfo' d SameInfoWildcardCls), Show (SemanticInfo' d SameInfoNameCls), Show (SemanticInfo' d SameInfoExprCls), Show (SemanticInfo' d SameInfoImportCls), Show (SemanticInfo' d SameInfoModuleCls), Show (SemanticInfo' d SameInfoWildcardCls))
- type DomainWith e d = (Data (SemanticInfo' d (SemaInfoClassify e)), Show (SemanticInfo' d (SemaInfoClassify e)), Domain d)
- class HasRange a where
- class (Typeable stage, Data stage, Data (SpanInfo stage), Data (ListInfo stage), Data (OptionalInfo stage), Show (SpanInfo stage), Show (ListInfo stage), Show (OptionalInfo stage), HasRange (SpanInfo stage), HasRange (ListInfo stage), HasRange (OptionalInfo stage)) => SourceInfo stage where
- shortShowSpan :: SrcSpan -> String
- shortShowSpanWithFile :: SrcSpan -> String
- shortShowLoc :: SrcLoc -> String
- class SourceInfo stage => RangeInfo stage where
- data NodeInfo sema src = NodeInfo {
- _semanticInfo :: sema
- _sourceInfo :: src
- sourceInfo :: forall sema src src'. Lens (NodeInfo sema src) (NodeInfo sema src') src src'
- semanticInfo :: forall sema src sema'. Lens (NodeInfo sema src) (NodeInfo sema' src) sema sema'
- data Ann elem dom stage = Ann {
- _annotation :: NodeInfo (SemanticInfo dom elem) (SpanInfo stage)
- _element :: elem dom stage
- element :: forall elem dom stage. Lens (Ann elem dom stage) (Ann elem dom stage) (elem dom stage) (elem dom stage)
- annotation :: forall elem dom stage. Lens (Ann elem dom stage) (Ann elem dom stage) (NodeInfo (SemanticInfo dom elem) (SpanInfo stage)) (NodeInfo (SemanticInfo dom elem) (SpanInfo stage))
- data AnnListG elem dom stage = AnnListG {
- _annListAnnot :: NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)
- _annListElems :: [Ann elem dom stage]
- annListElems :: forall elem dom stage. Lens (AnnListG elem dom stage) (AnnListG elem dom stage) [Ann elem dom stage] [Ann elem dom stage]
- annListAnnot :: forall elem dom stage. Lens (AnnListG elem dom stage) (AnnListG elem dom stage) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage))
- annList :: Traversal (AnnListG e d s) (AnnListG e d s) (Ann e d s) (Ann e d s)
- data AnnMaybeG elem dom stage = AnnMaybeG {
- _annMaybeAnnot :: NodeInfo (SemanticInfo dom (AnnMaybeG elem)) (OptionalInfo stage)
- _annMaybe :: Maybe (Ann elem dom stage)
- annMaybeAnnot :: forall elem dom stage. Lens (AnnMaybeG elem dom stage) (AnnMaybeG elem dom stage) (NodeInfo (SemanticInfo dom (AnnMaybeG elem)) (OptionalInfo stage)) (NodeInfo (SemanticInfo dom (AnnMaybeG elem)) (OptionalInfo stage))
- annMaybe :: forall elem dom stage. Lens (AnnMaybeG elem dom stage) (AnnMaybeG elem dom stage) (Maybe (Ann elem dom stage)) (Maybe (Ann elem dom stage))
- class HasSourceInfo e where
- type SourceInfoType e :: *
- annJust :: Partial (AnnMaybeG e d s) (AnnMaybeG e d s) (Ann e d s) (Ann e d s)
- annNil :: NodeInfo (SemanticInfo d (AnnListG e)) (ListInfo s) -> AnnListG e d s
- isAnnNothing :: AnnMaybeG e d s -> Bool
- isAnnJust :: AnnMaybeG e d s -> Bool
- annLength :: AnnListG e d s -> Int
- annNothing :: NodeInfo (SemanticInfo d (AnnMaybeG e)) (OptionalInfo s) -> AnnMaybeG e d s
- class ApplySemaChange cls where
- class ApplySemaChange (SemaInfoClassify a) => SemanticTraversal a where
- data SemaTrf f dom1 dom2 = SemaTrf {
- trfSemaNameCls :: SemanticInfo' dom1 SameInfoNameCls -> f (SemanticInfo' dom2 SameInfoNameCls)
- trfSemaExprCls :: SemanticInfo' dom1 SameInfoExprCls -> f (SemanticInfo' dom2 SameInfoExprCls)
- trfSemaImportCls :: SemanticInfo' dom1 SameInfoImportCls -> f (SemanticInfo' dom2 SameInfoImportCls)
- trfSemaModuleCls :: SemanticInfo' dom1 SameInfoModuleCls -> f (SemanticInfo' dom2 SameInfoModuleCls)
- trfSemaWildcardCls :: SemanticInfo' dom1 SameInfoWildcardCls -> f (SemanticInfo' dom2 SameInfoWildcardCls)
- trfSemaDefault :: SemanticInfo' dom1 SameInfoDefaultCls -> f (SemanticInfo' dom2 SameInfoDefaultCls)
- class SourceInfoTraversal a where
- data SourceInfoTrf f st1 st2 = SourceInfoTrf {
- trfSpanInfo :: SpanInfo st1 -> f (SpanInfo st2)
- trfListInfo :: ListInfo st1 -> f (ListInfo st2)
- trfOptionalInfo :: OptionalInfo st1 -> f (OptionalInfo st2)
Annotation type resolution
data RangeStage Source #
A stage in which the nodes are marked with the ranges in the source files which contain the source code of the given AST element.
Instances
data NormRangeStage Source #
A stage in which the nodes are still marked with ranges, but these ranges are normalized. Optional and list elements also have ranges in that state.
Instances
data RngTemplateStage Source #
A stage in which AST elements are marked with templates. These templates are hierarchical, and contain the places of the children elements of the node.
Instances
data SrcTemplateStage Source #
A stage where the annotation controls how the original source code can be retrieved from the AST. A source template is assigned to each node. It has holes where the content of an other node should be printed and ranges for the source code of the node.
Instances
With this domain, semantic information can be parameterized. In practice it is only used if the compilation cannot proceed past the type checking phase.
Instances
(Data name, Typeable * name) => Data (Dom name) Source # | |
type SemanticInfo' (Dom n) SameInfoDefaultCls Source # | |
type SemanticInfo' (Dom n) SameInfoWildcardCls Source # | |
type SemanticInfo' (Dom n) SameInfoModuleCls Source # | |
type SemanticInfo' (Dom n) SameInfoImportCls Source # | |
type SemanticInfo' (Dom n) SameInfoExprCls Source # | |
type SemanticInfo' (Dom n) SameInfoNameCls Source # | |
Instances
type SemanticInfo (domain :: *) (node :: * -> * -> *) = SemanticInfo' domain (SemaInfoClassify node) Source #
data SameInfoNameCls Source #
Instances
data SameInfoExprCls Source #
Instances
data SameInfoImportCls Source #
Instances
data SameInfoModuleCls Source #
Instances
data SameInfoDefaultCls Source #
Instances
data SameInfoWildcardCls Source #
Instances
type family SemanticInfo' (domain :: *) (nodecls :: *) Source #
Instances
type SemanticInfo' IdDom SameInfoWildcardCls Source # | |
type SemanticInfo' IdDom SameInfoDefaultCls Source # | |
type SemanticInfo' IdDom SameInfoModuleCls Source # | |
type SemanticInfo' IdDom SameInfoImportCls Source # | |
type SemanticInfo' IdDom SameInfoExprCls Source # | |
type SemanticInfo' IdDom SameInfoNameCls Source # | |
type SemanticInfo' (Dom n) SameInfoDefaultCls Source # | |
type SemanticInfo' (Dom n) SameInfoWildcardCls Source # | |
type SemanticInfo' (Dom n) SameInfoModuleCls Source # | |
type SemanticInfo' (Dom n) SameInfoImportCls Source # | |
type SemanticInfo' (Dom n) SameInfoExprCls Source # | |
type SemanticInfo' (Dom n) SameInfoNameCls Source # | |
type Domain d = (Typeable d, Data d, SemanticInfo' d SameInfoDefaultCls ~ NoSemanticInfo, Data (SemanticInfo' d SameInfoNameCls), Data (SemanticInfo' d SameInfoExprCls), Data (SemanticInfo' d SameInfoImportCls), Data (SemanticInfo' d SameInfoModuleCls), Data (SemanticInfo' d SameInfoWildcardCls), Show (SemanticInfo' d SameInfoNameCls), Show (SemanticInfo' d SameInfoExprCls), Show (SemanticInfo' d SameInfoImportCls), Show (SemanticInfo' d SameInfoModuleCls), Show (SemanticInfo' d SameInfoWildcardCls)) Source #
A semantic domain for the AST. The semantic domain maps semantic information for the different types of nodes in the AST. The kind of semantic domain for an AST depends on which stages of the compilation did it pass. However after transforming the GHC representation to our AST, the domain keeps the same. The domain is not applied to the AST elements that are generated while refactoring.
type DomainWith e d = (Data (SemanticInfo' d (SemaInfoClassify e)), Show (SemanticInfo' d (SemaInfoClassify e)), Domain d) Source #
class HasRange a where Source #
Extracts or modifies the concrete range corresponding to a given source info. In case of lists and optional elements, it may not contain the elements inside.
Instances
HasRange (SpanInfo NormRangeStage) Source # | |
HasRange (SpanInfo RangeStage) Source # | |
HasRange (ListInfo NormRangeStage) Source # | |
HasRange (ListInfo RangeStage) Source # | |
HasRange (OptionalInfo NormRangeStage) Source # | |
HasRange (OptionalInfo RangeStage) Source # | |
SourceInfo stage => HasRange (Ann elem dom stage) Source # | |
SourceInfo stage => HasRange (AnnListG elem dom stage) Source # | |
SourceInfo stage => HasRange (AnnMaybeG elem dom stage) Source # | |
class (Typeable stage, Data stage, Data (SpanInfo stage), Data (ListInfo stage), Data (OptionalInfo stage), Show (SpanInfo stage), Show (ListInfo stage), Show (OptionalInfo stage), HasRange (SpanInfo stage), HasRange (ListInfo stage), HasRange (OptionalInfo stage)) => SourceInfo stage Source #
Class for source information stages
Associated Types
data SpanInfo stage :: * Source #
UType of source info for normal AST elements
data ListInfo stage :: * Source #
UType of source info for lists of AST elements
data OptionalInfo stage :: * Source #
UType of source info for optional AST elements
Instances
shortShowSpan :: SrcSpan -> String Source #
A short form of showing a range, without file name, for debugging purposes.
shortShowLoc :: SrcLoc -> String Source #
A short form of showing a range, without file name, for debugging purposes.
class SourceInfo stage => RangeInfo stage where Source #
A class for marking a source information stage. All programs, regardless of correct Haskell programs or not, must go through these stages to be refactored.
Minimal complete definition
Methods
nodeSpan :: Simple Lens (SpanInfo stage) SrcSpan Source #
listPos :: Simple Lens (ListInfo stage) SrcLoc Source #
optionalPos :: Simple Lens (OptionalInfo stage) SrcLoc Source #
Instances
Annotations
data NodeInfo sema src Source #
Semantic and source code related information for an AST node.
Constructors
NodeInfo | |
Fields
|
semanticInfo :: forall sema src sema'. Lens (NodeInfo sema src) (NodeInfo sema' src) sema sema' Source #
data Ann elem dom stage Source #
An element of the AST keeping extra information.
Constructors
Ann | |
Fields
|
Instances
SourceInfoTraversal e => SourceInfoTraversal (Ann e) Source # | |
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (Ann e) Source # | |
SourceInfo stage => HasRange (Ann elem dom stage) Source # | |
HasSourceInfo (Ann elem dom stage) Source # | |
HasImplicitFieldsInfo dom => HasImplicitFieldsInfo' (Ann UFieldWildcard dom st) Source # | |
HasImportInfo dom => HasImportInfo' (Ann UImportDecl dom st) Source # | |
HasModuleInfo dom => HasModuleInfo' (Ann UModule dom st) Source # | |
HasDefiningInfo dom => HasDefiningInfo' (Ann UQualifiedName dom st) Source # | |
HasScopeInfo dom => HasScopeInfo' (Ann UExpr dom st) Source # | |
HasScopeInfo dom => HasScopeInfo' (Ann UQualifiedName dom st) Source # | |
HasFixityInfo dom => HasFixityInfo' (Ann UQualifiedName dom st) Source # | |
HasIdInfo dom => HasIdInfo' (Ann UQualifiedName dom st) Source # | |
HasNameInfo dom => HasNameInfo' (Ann UQualifiedName dom st) Source # | |
type Rep (Ann e dom stage) # | |
type SourceInfoType (Ann elem dom stage) Source # | |
element :: forall elem dom stage. Lens (Ann elem dom stage) (Ann elem dom stage) (elem dom stage) (elem dom stage) Source #
annotation :: forall elem dom stage. Lens (Ann elem dom stage) (Ann elem dom stage) (NodeInfo (SemanticInfo dom elem) (SpanInfo stage)) (NodeInfo (SemanticInfo dom elem) (SpanInfo stage)) Source #
data AnnListG elem dom stage Source #
A list of AST elements
Constructors
AnnListG | |
Fields
|
Instances
SourceInfoTraversal e => SourceInfoTraversal (AnnListG e) Source # | |
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnListG e) Source # | |
SourceInfo stage => HasRange (AnnListG elem dom stage) Source # | |
HasSourceInfo (AnnListG elem dom stage) Source # | |
type Rep (AnnListG e dom stage) # | |
type SourceInfoType (AnnListG elem dom stage) Source # | |
annListElems :: forall elem dom stage. Lens (AnnListG elem dom stage) (AnnListG elem dom stage) [Ann elem dom stage] [Ann elem dom stage] Source #
annListAnnot :: forall elem dom stage. Lens (AnnListG elem dom stage) (AnnListG elem dom stage) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) Source #
data AnnMaybeG elem dom stage Source #
An optional AST element
Constructors
AnnMaybeG | |
Fields
|
Instances
SourceInfoTraversal e => SourceInfoTraversal (AnnMaybeG e) Source # | |
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnMaybeG e) Source # | |
SourceInfo stage => HasRange (AnnMaybeG elem dom stage) Source # | |
HasSourceInfo (AnnMaybeG elem dom stage) Source # | |
type Rep (AnnMaybeG e dom stage) # | |
type SourceInfoType (AnnMaybeG elem dom stage) Source # | |
annMaybeAnnot :: forall elem dom stage. Lens (AnnMaybeG elem dom stage) (AnnMaybeG elem dom stage) (NodeInfo (SemanticInfo dom (AnnMaybeG elem)) (OptionalInfo stage)) (NodeInfo (SemanticInfo dom (AnnMaybeG elem)) (OptionalInfo stage)) Source #
annMaybe :: forall elem dom stage. Lens (AnnMaybeG elem dom stage) (AnnMaybeG elem dom stage) (Maybe (Ann elem dom stage)) (Maybe (Ann elem dom stage)) Source #
class HasSourceInfo e where Source #
Minimal complete definition
Associated Types
type SourceInfoType e :: * Source #
Instances
HasSourceInfo (Ann elem dom stage) Source # | |
HasSourceInfo (AnnListG elem dom stage) Source # | |
HasSourceInfo (AnnMaybeG elem dom stage) Source # | |
annNil :: NodeInfo (SemanticInfo d (AnnListG e)) (ListInfo s) -> AnnListG e d s Source #
An empty list of AST elements
isAnnNothing :: AnnMaybeG e d s -> Bool Source #
annNothing :: NodeInfo (SemanticInfo d (AnnMaybeG e)) (OptionalInfo s) -> AnnMaybeG e d s Source #
A non-existing AST part
Info types
class ApplySemaChange cls where Source #
A class for changing semantic information throught the AST.
Minimal complete definition
Methods
appSemaChange :: SemaTrf f dom1 dom2 -> SemanticInfo' dom1 cls -> f (SemanticInfo' dom2 cls) Source #
class ApplySemaChange (SemaInfoClassify a) => SemanticTraversal a where Source #
A class for traversing semantic information in an AST
Minimal complete definition
Methods
semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> a dom1 st -> f (a dom2 st) Source #
Instances
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (Ann e) Source # | |
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnListG e) Source # | |
(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnMaybeG e) Source # | |
data SemaTrf f dom1 dom2 Source #
A transformation on the possible semantic informations for a given domain
Constructors
SemaTrf | |
Fields
|
class SourceInfoTraversal a where Source #
A class for traversing source information in an AST
Minimal complete definition
sourceInfoTraverseUp, sourceInfoTraverseDown, sourceInfoTraverse
Methods
sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> a dom st1 -> f (a dom st2) Source #
sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> a dom st1 -> f (a dom st2) Source #
sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> a dom st1 -> f (a dom st2) Source #
Instances
SourceInfoTraversal e => SourceInfoTraversal (Ann e) Source # | |
SourceInfoTraversal e => SourceInfoTraversal (AnnListG e) Source # | |
SourceInfoTraversal e => SourceInfoTraversal (AnnMaybeG e) Source # | |
data SourceInfoTrf f st1 st2 Source #
A transformation on the possible source informations
Constructors
SourceInfoTrf | |
Fields
|