haskell-tools-refactor-0.7.0.0: Refactoring Tool for Haskell

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Refactor

Description

Defines the API for refactorings

Synopsis

Documentation

data Ann elem dom stage :: (* -> * -> *) -> * -> * -> * #

An element of the AST keeping extra information.

Instances

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

Methods

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

SourceInfoTraversal e => SourceInfoTraversal (Ann e) 

Methods

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

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

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

HasNameInfo dom => HasNameInfo' (Ann UQualifiedName dom st) 
HasIdInfo dom => HasIdInfo' (Ann UQualifiedName dom st) 

Methods

semanticsId :: Ann UQualifiedName dom st -> Id #

HasFixityInfo dom => HasFixityInfo' (Ann UQualifiedName dom st) 
HasScopeInfo dom => HasScopeInfo' (Ann UExpr dom st) 

Methods

semanticsScope :: Ann UExpr dom st -> Scope #

HasScopeInfo dom => HasScopeInfo' (Ann UQualifiedName dom st) 
HasDefiningInfo dom => HasDefiningInfo' (Ann UQualifiedName dom st) 
HasModuleInfo dom => HasModuleInfo' (Ann UModule dom st) 
HasImportInfo dom => HasImportInfo' (Ann UImportDecl dom st) 
HasImplicitFieldsInfo dom => HasImplicitFieldsInfo' (Ann UFieldWildcard dom st) 
HasSourceInfo (Ann elem dom stage) 

Associated Types

type SourceInfoType (Ann elem dom stage) :: * #

Methods

srcInfo :: Simple Lens (Ann elem dom stage) (SourceInfoType (Ann elem dom stage)) #

SourceInfo stage => HasRange (Ann elem dom stage) 

Methods

getRange :: Ann elem dom stage -> SrcSpan #

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

type Rep (Ann e dom stage) 
type Rep (Ann e dom stage) = D1 (MetaData "Ann" "Language.Haskell.Tools.AST.Ann" "haskell-tools-ast-0.7.0.0-8c6uZRwocvGB0Wdu7cGYu1" 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)))))
type SourceInfoType (Ann elem dom stage) 
type SourceInfoType (Ann elem dom stage) = SpanInfo stage

class HasSourceInfo e where #

Minimal complete definition

srcInfo

Associated Types

type SourceInfoType e :: * #

Instances

HasSourceInfo (AnnMaybeG elem dom stage) 

Associated Types

type SourceInfoType (AnnMaybeG elem dom stage) :: * #

Methods

srcInfo :: Simple Lens (AnnMaybeG elem dom stage) (SourceInfoType (AnnMaybeG elem dom stage)) #

HasSourceInfo (AnnListG elem dom stage) 

Associated Types

type SourceInfoType (AnnListG elem dom stage) :: * #

Methods

srcInfo :: Simple Lens (AnnListG elem dom stage) (SourceInfoType (AnnListG elem dom stage)) #

HasSourceInfo (Ann elem dom stage) 

Associated Types

type SourceInfoType (Ann elem dom stage) :: * #

Methods

srcInfo :: Simple Lens (Ann elem dom stage) (SourceInfoType (Ann elem dom stage)) #

class HasRange a where #

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 #

setRange :: SrcSpan -> a -> a #

Instances

HasRange (OptionalInfo RangeStage) 
HasRange (OptionalInfo NormRangeStage) 
HasRange (ListInfo RangeStage) 
HasRange (ListInfo NormRangeStage) 
HasRange (SpanInfo RangeStage) 
HasRange (SpanInfo NormRangeStage) 
SourceInfo stage => HasRange (AnnMaybeG elem dom stage) 

Methods

getRange :: AnnMaybeG elem dom stage -> SrcSpan #

setRange :: SrcSpan -> AnnMaybeG elem dom stage -> AnnMaybeG elem dom stage #

SourceInfo stage => HasRange (AnnListG elem dom stage) 

Methods

getRange :: AnnListG elem dom stage -> SrcSpan #

setRange :: SrcSpan -> AnnListG elem dom stage -> AnnListG elem dom stage #

SourceInfo stage => HasRange (Ann elem dom stage) 

Methods

getRange :: Ann elem dom stage -> SrcSpan #

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

annListElems :: RefMonads w r => Reference w r (MU *) (MU *) (AnnListG elem0 dom0 stage0) (AnnListG elem0 dom0 stage0) [Ann elem0 dom0 stage0] [Ann elem0 dom0 stage0] #

annListAnnot :: RefMonads w r => Reference w r (MU *) (MU *) (AnnListG elem0 dom0 stage0) (AnnListG elem0 dom0 stage0) (NodeInfo (SemanticInfo dom0 (AnnListG elem0)) (ListInfo stage0)) (NodeInfo (SemanticInfo dom0 (AnnListG elem0)) (ListInfo stage0)) #

annList :: (RefMonads w r, MonadPlus r, Morph Maybe r, Morph [] r) => Reference w r (MU *) (MU *) (AnnListG e d s) (AnnListG e d s) (Ann e d s) (Ann e d s) #

annJust :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r (MU *) (MU *) (AnnMaybeG e d s) (AnnMaybeG e d s) (Ann e d s) (Ann e d s) #

annMaybe :: RefMonads w r => Reference w r (MU *) (MU *) (AnnMaybeG elem0 dom0 stage0) (AnnMaybeG elem0 dom0 stage0) (Maybe (Ann elem0 dom0 stage0)) (Maybe (Ann elem0 dom0 stage0)) #

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 #

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

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.

shortShowSpan :: SrcSpan -> String #

A short form of showing a range, without file name, for debugging purposes.

data SrcTemplateStage :: * #

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 

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 #

AfterBefore (OptionalInfo SrcTemplateStage) 
AfterBefore (ListInfo SrcTemplateStage) 
RelativeIndent (OptionalInfo SrcTemplateStage) 
RelativeIndent (ListInfo SrcTemplateStage) 
RelativeIndent (SpanInfo SrcTemplateStage) 
MinimumIndent (OptionalInfo SrcTemplateStage) 
MinimumIndent (ListInfo SrcTemplateStage) 
MinimumIndent (SpanInfo SrcTemplateStage) 
data OptionalInfo SrcTemplateStage 
data ListInfo SrcTemplateStage 
data SpanInfo SrcTemplateStage 

class SourceInfoTraversal a where #

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) #

sourceInfoTraverseDown :: Monad f => SourceInfoTrf f st1 st2 -> f () -> f () -> a dom st1 -> f (a dom st2) #

sourceInfoTraverse :: Monad f => SourceInfoTrf f st1 st2 -> a dom st1 -> f (a dom st2) #

Instances

SourceInfoTraversal e => SourceInfoTraversal (AnnMaybeG e) 

Methods

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

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

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

SourceInfoTraversal e => SourceInfoTraversal (AnnListG e) 

Methods

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

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

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

SourceInfoTraversal e => SourceInfoTraversal (Ann e) 

Methods

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

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

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

data SourceTemplateTextElem :: * #

Instances

Eq SourceTemplateTextElem 
Data SourceTemplateTextElem 

Methods

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

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

toConstr :: SourceTemplateTextElem -> Constr #

dataTypeOf :: SourceTemplateTextElem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceTemplateTextElem 
Show SourceTemplateTextElem