haskell-tools-ast-0.2.0.0: Haskell AST for efficient tooling

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.Ann

Contents

Description

Parts of AST representation for keeping extra data

Synopsis

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 RangeStage Source # 

Methods

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

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

toConstr :: RangeStage -> Constr #

dataTypeOf :: RangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

RangeInfo RangeStage Source # 
SourceInfo RangeStage Source # 
Data (SpanInfo RangeStage) Source # 

Methods

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

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

toConstr :: SpanInfo RangeStage -> Constr #

dataTypeOf :: SpanInfo RangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ListInfo RangeStage) Source # 

Methods

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

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

toConstr :: ListInfo RangeStage -> Constr #

dataTypeOf :: ListInfo RangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (OptionalInfo RangeStage) Source # 

Methods

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

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

toConstr :: OptionalInfo RangeStage -> Constr #

dataTypeOf :: OptionalInfo RangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (SpanInfo RangeStage) Source # 
Show (ListInfo RangeStage) Source # 
Show (OptionalInfo RangeStage) Source # 
HasRange (SpanInfo RangeStage) Source # 
HasRange (ListInfo RangeStage) Source # 
HasRange (OptionalInfo RangeStage) Source # 
data SpanInfo RangeStage Source # 
data ListInfo RangeStage Source # 
data OptionalInfo RangeStage Source # 

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 NormRangeStage Source # 

Methods

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

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

toConstr :: NormRangeStage -> Constr #

dataTypeOf :: NormRangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

SourceInfo NormRangeStage Source # 
Data (SpanInfo NormRangeStage) Source # 

Methods

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

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

toConstr :: SpanInfo NormRangeStage -> Constr #

dataTypeOf :: SpanInfo NormRangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ListInfo NormRangeStage) Source # 

Methods

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

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

toConstr :: ListInfo NormRangeStage -> Constr #

dataTypeOf :: ListInfo NormRangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (OptionalInfo NormRangeStage) Source # 

Methods

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

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

toConstr :: OptionalInfo NormRangeStage -> Constr #

dataTypeOf :: OptionalInfo NormRangeStage -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (SpanInfo NormRangeStage) Source # 
Show (ListInfo NormRangeStage) Source # 
Show (OptionalInfo NormRangeStage) Source # 
HasRange (SpanInfo NormRangeStage) Source # 
HasRange (ListInfo NormRangeStage) Source # 
HasRange (OptionalInfo NormRangeStage) Source # 
data SpanInfo NormRangeStage Source # 
data ListInfo NormRangeStage Source # 
data OptionalInfo NormRangeStage Source # 

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 RngTemplateStage Source # 

Methods

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

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

toConstr :: RngTemplateStage -> Constr #

dataTypeOf :: RngTemplateStage -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Data SrcTemplateStage Source # 

Methods

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

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

toConstr :: SrcTemplateStage -> Constr #

dataTypeOf :: SrcTemplateStage -> DataType #

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

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

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

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

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

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

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

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

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

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

data Dom name Source #

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 # 

Methods

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

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

toConstr :: Dom name -> Constr #

dataTypeOf :: Dom name -> DataType #

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

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

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

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

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

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

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

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

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

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

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 # 

data IdDom Source #

Instances

Data IdDom Source # 

Methods

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

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

toConstr :: IdDom -> Constr #

dataTypeOf :: IdDom -> DataType #

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

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

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

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

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

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

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

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

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

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

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 domain node = SemanticInfo' domain (SemaInfoClassify node) Source #

class (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)) => Domain d Source #

Class for domain configuration markers

Instances

(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)) => Domain d 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.

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.

Minimal complete definition

getRange, setRange

Methods

getRange :: a -> SrcSpan Source #

setRange :: SrcSpan -> a -> a Source #

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 # 

Methods

getRange :: Ann elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> Ann elem dom stage -> Ann elem dom stage Source #

SourceInfo stage => HasRange (AnnList elem dom stage) Source # 

Methods

getRange :: AnnList elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> AnnList elem dom stage -> AnnList elem dom stage Source #

SourceInfo stage => HasRange (AnnMaybe elem dom stage) Source # 

Methods

getRange :: AnnMaybe elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> AnnMaybe elem dom stage -> AnnMaybe 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 #

Type of source info for normal AST elements

data ListInfo stage :: * Source #

Type of source info for lists of AST elements

data OptionalInfo stage :: * Source #

Type of source info for optional AST elements

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

nodeSpan, listPos, optionalPos

Annotations

data Ann elem dom stage Source #

An element of the AST keeping extra information.

Constructors

Ann 

Fields

Instances

SourceInfoTraversal e => SourceInfoTraversal (Ann e) Source # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> Ann e dom st1 -> f (Ann e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> Ann e dom st1 -> f (Ann e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> Ann e dom st1 -> f (Ann e dom st2) Source #

(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (Ann e) Source # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> Ann e dom1 st -> f (Ann e dom2 st) Source #

SourceInfo stage => HasRange (Ann elem dom stage) Source # 

Methods

getRange :: Ann elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> Ann elem dom stage -> Ann elem dom stage Source #

type Rep (Ann e dom stage) Source # 
type Rep (Ann e dom stage) = D1 (MetaData "Ann" "Language.Haskell.Tools.AST.Ann" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "Ann" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_annotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NodeInfo (SemanticInfo dom e) (SpanInfo stage)))) (S1 (MetaSel (Just Symbol "_element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (e dom stage)))))

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 AnnList elem dom stage Source #

A list of AST elements

Constructors

AnnList 

Fields

Instances

SourceInfoTraversal e => SourceInfoTraversal (AnnList e) Source # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnList e) Source # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> AnnList e dom1 st -> f (AnnList e dom2 st) Source #

SourceInfo stage => HasRange (AnnList elem dom stage) Source # 

Methods

getRange :: AnnList elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> AnnList elem dom stage -> AnnList elem dom stage Source #

type Rep (AnnList e dom stage) Source # 
type Rep (AnnList e dom stage) = D1 (MetaData "AnnList" "Language.Haskell.Tools.AST.Ann" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "AnnList" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_annListAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NodeInfo (SemanticInfo dom (AnnList e)) (ListInfo stage)))) (S1 (MetaSel (Just Symbol "_annListElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Ann e dom stage]))))

annListElems :: forall elem dom stage. Lens (AnnList elem dom stage) (AnnList elem dom stage) [Ann elem dom stage] [Ann elem dom stage] Source #

annListAnnot :: forall elem dom stage. Lens (AnnList elem dom stage) (AnnList elem dom stage) (NodeInfo (SemanticInfo dom (AnnList elem)) (ListInfo stage)) (NodeInfo (SemanticInfo dom (AnnList elem)) (ListInfo stage)) Source #

annList :: Traversal (AnnList e d s) (AnnList e d s) (Ann e d s) (Ann e d s) Source #

data AnnMaybe elem dom stage Source #

An optional AST element

Constructors

AnnMaybe 

Fields

Instances

SourceInfoTraversal e => SourceInfoTraversal (AnnMaybe e) Source # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnMaybe e) Source # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> AnnMaybe e dom1 st -> f (AnnMaybe e dom2 st) Source #

SourceInfo stage => HasRange (AnnMaybe elem dom stage) Source # 

Methods

getRange :: AnnMaybe elem dom stage -> SrcSpan Source #

setRange :: SrcSpan -> AnnMaybe elem dom stage -> AnnMaybe elem dom stage Source #

type Rep (AnnMaybe e dom stage) Source # 
type Rep (AnnMaybe e dom stage) = D1 (MetaData "AnnMaybe" "Language.Haskell.Tools.AST.Ann" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "AnnMaybe" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_annMaybeAnnot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NodeInfo (SemanticInfo dom (AnnMaybe e)) (OptionalInfo stage)))) (S1 (MetaSel (Just Symbol "_annMaybe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Ann e dom stage))))))

annMaybeAnnot :: forall elem dom stage. Lens (AnnMaybe elem dom stage) (AnnMaybe elem dom stage) (NodeInfo (SemanticInfo dom (AnnMaybe elem)) (OptionalInfo stage)) (NodeInfo (SemanticInfo dom (AnnMaybe elem)) (OptionalInfo stage)) Source #

annMaybe :: forall elem dom stage. Lens (AnnMaybe elem dom stage) (AnnMaybe elem dom stage) (Maybe (Ann elem dom stage)) (Maybe (Ann elem dom stage)) Source #

annJust :: Partial (AnnMaybe e d s) (AnnMaybe e d s) (Ann e d s) (Ann e d s) Source #

annNil :: NodeInfo (SemanticInfo d (AnnList e)) (ListInfo s) -> AnnList e d s Source #

An empty list of AST elements

annNothing :: NodeInfo (SemanticInfo d (AnnMaybe e)) (OptionalInfo s) -> AnnMaybe e d s Source #

A non-existing AST part

Info types

class ApplySemaChange (SemaInfoClassify a) => SemanticTraversal a where Source #

A class for traversing semantic information in an AST

Minimal complete definition

semaTraverse

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 # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> Ann e dom1 st -> f (Ann e dom2 st) Source #

(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnList e) Source # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> AnnList e dom1 st -> f (AnnList e dom2 st) Source #

(ApplySemaChange (SemaInfoClassify e), SemanticTraversal e) => SemanticTraversal (AnnMaybe e) Source # 

Methods

semaTraverse :: Monad f => SemaTrf f dom1 dom2 -> AnnMaybe e dom1 st -> f (AnnMaybe e dom2 st) Source #

class SourceInfoTraversal a where Source #

A class for traversing source information in an AST

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 # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> Ann e dom st1 -> f (Ann e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> Ann e dom st1 -> f (Ann e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> Ann e dom st1 -> f (Ann e dom st2) Source #

SourceInfoTraversal e => SourceInfoTraversal (AnnList e) Source # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> AnnList e dom st1 -> f (AnnList e dom st2) Source #

SourceInfoTraversal e => SourceInfoTraversal (AnnMaybe e) Source # 

Methods

sourceInfoTraverseUp :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> AnnMaybe e dom st1 -> f (AnnMaybe e dom st2) Source #

data SourceInfoTrf f st1 st2 Source #

A transformation on the possible source informations

Constructors

SourceInfoTrf 

Fields