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

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.Helpers

Description

Helper functions for using the AST.

Synopsis

Documentation

nameString :: QualifiedName dom stage -> String Source #

The occurrence of the name.

nameElements :: QualifiedName dom stage -> [String] Source #

The qualifiers and the unqualified name

nameQualifier :: QualifiedName dom stage -> [String] Source #

The qualifier of the name

importIsExact :: ImportDecl dom stage -> Bool Source #

Does the import declaration import only the explicitly listed elements?

importIsHiding :: ImportDecl dom stage -> Bool Source #

Does the import declaration has a hiding clause?

importExacts :: Simple Traversal (ImportDecl dom stage) (IESpec dom stage) Source #

All elements that are explicitly listed to be imported in the import declaration

importHidings :: Simple Traversal (ImportDecl dom stage) (IESpec dom stage) Source #

All elements that are hidden in an import

importQualifiers :: ImportDecl dom stage -> [[String]] Source #

Possible qualifiers to use imported definitions

typeParams :: Simple Traversal (Ann Type dom stage) (Ann Type dom stage) Source #

semantics :: Simple Lens (Ann elem dom stage) (SemanticInfo dom elem) Source #

Access the semantic information of an AST node.

class BindingElem d where Source #

A type class for transformations that work on both top-level and local definitions

Methods

sigBind :: Simple Partial (d dom stage) (Ann TypeSignature dom stage) Source #

valBind :: Simple Partial (d dom stage) (Ann ValueBind dom stage) Source #

createTypeSig :: Ann TypeSignature dom stage -> d dom stage Source #

createBinding :: Ann ValueBind dom stage -> d dom stage Source #

isTypeSig :: d dom stage -> Bool Source #

isBinding :: d dom stage -> Bool Source #

Instances

BindingElem LocalBind Source # 

Methods

sigBind :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r (MU *) (MU *) (LocalBind dom stage) (LocalBind dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

valBind :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r (MU *) (MU *) (LocalBind dom stage) (LocalBind dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

createTypeSig :: Ann TypeSignature dom stage -> LocalBind dom stage Source #

createBinding :: Ann ValueBind dom stage -> LocalBind dom stage Source #

isTypeSig :: LocalBind dom stage -> Bool Source #

isBinding :: LocalBind dom stage -> Bool Source #

BindingElem Decl Source # 

Methods

sigBind :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r (MU *) (MU *) (Decl dom stage) (Decl dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

valBind :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r (MU *) (MU *) (Decl dom stage) (Decl dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

createTypeSig :: Ann TypeSignature dom stage -> Decl dom stage Source #

createBinding :: Ann ValueBind dom stage -> Decl dom stage Source #

isTypeSig :: Decl dom stage -> Bool Source #

isBinding :: Decl dom stage -> Bool Source #

getValBindInList :: (BindingElem d, SourceInfo stage) => RealSrcSpan -> AnnList d dom stage -> Maybe (Ann ValueBind dom stage) Source #

nodesContaining :: (HasRange (inner dom stage), Biplate (node dom stage) (inner dom stage), SourceInfo stage) => RealSrcSpan -> Simple Traversal (node dom stage) (inner dom stage) Source #

Get all nodes that contain a given source range

isInside :: HasRange (inner dom stage) => RealSrcSpan -> inner dom stage -> Bool Source #

Return true if the node contains a given range

nodesContained :: (HasRange (inner dom stage), Biplate (node dom stage) (inner dom stage), SourceInfo stage) => RealSrcSpan -> Simple Traversal (node dom stage) (inner dom stage) Source #

Get all nodes that are contained in a given source range

isContained :: HasRange (inner dom stage) => RealSrcSpan -> inner dom stage -> Bool Source #

Return true if the node contains a given range

nodesWithRange :: (Biplate (Ann node dom stage) (Ann inner dom stage), SourceInfo stage) => RealSrcSpan -> Simple Traversal (Ann node dom stage) (Ann inner dom stage) Source #

Get the nodes that have exactly the given range

hasRange :: SourceInfo stage => RealSrcSpan -> Ann inner dom stage -> Bool Source #

True, if the node has the given range

getNodeContaining :: (Biplate (Ann node dom stage) (Ann inner dom stage), SourceInfo stage, HasRange (Ann inner dom stage)) => RealSrcSpan -> Ann node dom stage -> Maybe (Ann inner dom stage) Source #

Get the shortest source range that contains the given

compareRangeLength :: SrcSpan -> SrcSpan -> Ordering Source #

Compares two NESTED source spans based on their lengths

getNode :: (Biplate (Ann node dom stage) (Ann inner dom stage), SourceInfo stage) => RealSrcSpan -> Ann node dom stage -> Ann inner dom stage Source #