Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines the API for refactorings
- module Language.Haskell.Tools.AST.SemaInfoClasses
- module Language.Haskell.Tools.Rewrite
- module Language.Haskell.Tools.AST.References
- module Language.Haskell.Tools.AST.Helpers
- module Language.Haskell.Tools.Refactor.Utils.Monadic
- module Language.Haskell.Tools.Refactor.Utils.Helpers
- module Language.Haskell.Tools.Rewrite.ElementTypes
- module Language.Haskell.Tools.Refactor.Prepare
- module Language.Haskell.Tools.Refactor.Utils.Lists
- module Language.Haskell.Tools.Refactor.Utils.BindingElem
- module Language.Haskell.Tools.Refactor.Utils.Indentation
- module Language.Haskell.Tools.Refactor.Querying
- module Language.Haskell.Tools.Refactor.Refactoring
- module Language.Haskell.Tools.Refactor.Utils.Name
- module Language.Haskell.Tools.Refactor.Representation
- module Language.Haskell.Tools.Refactor.Monad
- module Language.Haskell.Tools.Refactor.Utils.Type
- module Language.Haskell.Tools.Refactor.Utils.TypeLookup
- module Language.Haskell.Tools.Refactor.Utils.NameLookup
- data Ann (elem :: * -> * -> *) dom stage :: (* -> * -> *) -> * -> * -> *
- class HasSourceInfo e where
- type SourceInfoType e :: *
- class HasRange a where
- annListElems :: RefMonads w r => Reference w r MU MU (AnnListG elem dom stage) (AnnListG elem dom stage) [Ann elem dom stage] [Ann elem dom stage]
- annListAnnot :: RefMonads w r => Reference w r MU MU (AnnListG elem dom stage) (AnnListG elem dom stage) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage))
- 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 elem dom stage) (AnnMaybeG elem dom stage) (Maybe (Ann elem dom stage)) (Maybe (Ann elem dom stage))
- isAnnNothing :: AnnMaybeG e d s -> Bool
- type Domain d = (Typeable * d, Data d, (~) * (SemanticInfo' d SemaInfoDefaultCls) NoSemanticInfo, Data (SemanticInfo' d SemaInfoNameCls), Data (SemanticInfo' d SemaInfoLitCls), Data (SemanticInfo' d SemaInfoExprCls), Data (SemanticInfo' d SemaInfoImportCls), Data (SemanticInfo' d SemaInfoModuleCls), Data (SemanticInfo' d SemaInfoWildcardCls))
- data Dom name :: * -> *
- data IdDom :: *
- shortShowSpan :: SrcSpan -> String
- shortShowSpanWithFile :: SrcSpan -> String
- data SrcTemplateStage :: *
- class SourceInfoTraversal (a :: * -> * -> *) where
- sourceTemplateNodeRange :: Simple Lens (SpanInfo SrcTemplateStage) SrcSpan
- sourceTemplateNodeElems :: Simple Lens (SpanInfo SrcTemplateStage) [SourceTemplateElem]
- sourceTemplateListRange :: Simple Lens (ListInfo SrcTemplateStage) SrcSpan
- srcTmpListBefore :: Simple Lens (ListInfo SrcTemplateStage) String
- srcTmpListAfter :: Simple Lens (ListInfo SrcTemplateStage) String
- srcTmpDefaultSeparator :: Simple Lens (ListInfo SrcTemplateStage) String
- srcTmpIndented :: Simple Lens (ListInfo SrcTemplateStage) (Maybe [Bool])
- srcTmpSeparators :: Simple Lens (ListInfo SrcTemplateStage) [([SourceTemplateTextElem], SrcSpan)]
- sourceTemplateOptRange :: Simple Lens (OptionalInfo SrcTemplateStage) SrcSpan
- srcTmpOptBefore :: Simple Lens (OptionalInfo SrcTemplateStage) String
- srcTmpOptAfter :: Simple Lens (OptionalInfo SrcTemplateStage) String
- data SourceTemplateTextElem :: *
- = NormalText { }
- | StayingText { }
- sourceTemplateText :: Lens SourceTemplateTextElem SourceTemplateTextElem String String
- data UnsupportedExtension = UnsupportedExtension String
- data SpliceInsertionProblem :: * = SpliceInsertionProblem SrcSpan String
- data ConvertionProblem :: *
- data TransformationProblem :: * = TransformationProblem String
- data BreakUpProblem :: * = BreakUpProblem {
- bupOuter :: RealSrcSpan
- bupInner :: SrcSpan
- bupSiblings :: [SrcSpan]
- data PrettyPrintProblem :: * = PrettyPrintProblem String
Documentation
data Ann (elem :: * -> * -> *) dom stage :: (* -> * -> *) -> * -> * -> * #
An element of the AST keeping extra information.
class HasSourceInfo e where #
type SourceInfoType e :: * #
srcInfo :: Simple Lens e (SourceInfoType e) #
HasSourceInfo (AnnMaybeG elem dom stage) | |
HasSourceInfo (AnnListG elem dom stage) | |
HasSourceInfo (Ann elem dom stage) | |
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.
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) | |
SourceInfo stage => HasRange (AnnListG elem dom stage) | |
SourceInfo stage => HasRange (Ann elem dom stage) | |
annListElems :: RefMonads w r => Reference w r MU MU (AnnListG elem dom stage) (AnnListG elem dom stage) [Ann elem dom stage] [Ann elem dom stage] #
annListAnnot :: RefMonads w r => Reference w r MU MU (AnnListG elem dom stage) (AnnListG elem dom stage) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) (NodeInfo (SemanticInfo dom (AnnListG elem)) (ListInfo stage)) #
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 elem dom stage) (AnnMaybeG elem dom stage) (Maybe (Ann elem dom stage)) (Maybe (Ann elem dom stage)) #
isAnnNothing :: AnnMaybeG e d s -> Bool #
type Domain d = (Typeable * d, Data d, (~) * (SemanticInfo' d SemaInfoDefaultCls) NoSemanticInfo, Data (SemanticInfo' d SemaInfoNameCls), Data (SemanticInfo' d SemaInfoLitCls), Data (SemanticInfo' d SemaInfoExprCls), Data (SemanticInfo' d SemaInfoImportCls), Data (SemanticInfo' d SemaInfoModuleCls), Data (SemanticInfo' d SemaInfoWildcardCls)) #
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 it passed. However after transforming the GHC representation to our AST, the domain stays the same. The domain is not applied to the AST elements that are generated while refactoring.
With this domain, semantic information can be parameterized. In practice it is only used if the compilation cannot proceed past the type checking phase.
(Data name, Typeable * name) => Data (Dom name) | |
type SemanticInfo' (Dom n) SemaInfoDefaultCls | |
type SemanticInfo' (Dom n) SemaInfoWildcardCls | |
type SemanticInfo' (Dom n) SemaInfoModuleCls | |
type SemanticInfo' (Dom n) SemaInfoImportCls | |
type SemanticInfo' (Dom n) SemaInfoExprCls | |
type SemanticInfo' (Dom n) SemaInfoLitCls | |
type SemanticInfo' (Dom n) SemaInfoNameCls | |
shortShowSpan :: SrcSpan -> String #
A short form of showing a range, without file name, for debugging purposes.
shortShowSpanWithFile :: SrcSpan -> String #
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.
Data 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
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) #
SourceInfoTraversal e => SourceInfoTraversal (AnnMaybeG e) | |
SourceInfoTraversal e => SourceInfoTraversal (AnnListG e) | |
SourceInfoTraversal e => SourceInfoTraversal (Ann e) | |
srcTmpIndented :: Simple Lens (ListInfo SrcTemplateStage) (Maybe [Bool]) #
data UnsupportedExtension Source #
data SpliceInsertionProblem :: * #
data ConvertionProblem :: * #
data TransformationProblem :: * #
data BreakUpProblem :: * #
BreakUpProblem | |
|