haskell-tools-ast-fromghc-0.2.0.0: Creating the Haskell-Tools AST from GHC's representations

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.FromGHC.Utils

Contents

Description

Utility functions for transforming the GHC AST representation into our own.

Synopsis

Documentation

createNameInfo :: n -> Trf (NameInfo n) Source #

Creates a semantic information for a name

createAmbigousNameInfo :: RdrName -> SrcSpan -> Trf (NameInfo n) Source #

Creates a semantic information for an ambiguous name (caused by field disambiguation for example)

createImplicitNameInfo :: String -> Trf (NameInfo n) Source #

Creates a semantic information for an implicit name

createImplicitFldInfo :: (GHCName n, HsHasName n) => (a -> n) -> [HsRecField n a] -> Trf ImplicitFieldInfo Source #

Creates a semantic information for an implicit name

createImportData :: (HsHasName n, GHCName n) => ImportDecl (Dom n) stage -> Trf (ImportInfo n) Source #

Adds semantic information to an impord declaration. See ImportInfo.

getImportedNames :: String -> Maybe String -> Trf (Module, [Name]) Source #

Get names that are imported from a given import

checkImportVisible :: (HsHasName n, GhcMonad m) => ImportDecl (Dom n) stage -> Name -> m Bool Source #

Check is a given name is imported from an import with given import specification.

ieSpecMatches :: (HsHasName n, GhcMonad m) => IESpec (Dom n) stage -> Name -> m Bool Source #

nothing :: String -> String -> Trf SrcLoc -> Trf (AnnMaybe e (Dom n) RangeStage) Source #

Creates a place for a missing node with a default location

makeList :: String -> Trf SrcLoc -> Trf [Ann e (Dom n) RangeStage] -> Trf (AnnList e (Dom n) RangeStage) Source #

Creates a place for a list of nodes with a default place if the list is empty.

makeIndentedList :: Trf SrcLoc -> Trf [Ann e (Dom n) RangeStage] -> Trf (AnnList e (Dom n) RangeStage) Source #

Creates a place for an indented list of nodes with a default place if the list is empty.

trfLoc :: (a -> Trf (b (Dom n) RangeStage)) -> Trf (SemanticInfo (Dom n) b) -> Located a -> Trf (Ann b (Dom n) RangeStage) Source #

Transform a located part of the AST by automatically transforming the location. Sets the source range for transforming children.

trfMaybe :: String -> String -> (Located a -> Trf (Ann e (Dom n) RangeStage)) -> Maybe (Located a) -> Trf (AnnMaybe e (Dom n) RangeStage) Source #

Transforms a possibly-missing node with the default location of the end of the focus.

trfMaybeDefault :: String -> String -> (Located a -> Trf (Ann e (Dom n) RangeStage)) -> Trf SrcLoc -> Maybe (Located a) -> Trf (AnnMaybe e (Dom n) RangeStage) Source #

Transforms a possibly-missing node with a default location

trfLocCorrect :: Trf (SemanticInfo (Dom n) b) -> (SrcSpan -> Trf SrcSpan) -> (a -> Trf (b (Dom n) RangeStage)) -> Located a -> Trf (Ann b (Dom n) RangeStage) Source #

Transform a located part of the AST by automatically transforming the location with correction by applying the given function. Sets the source range for transforming children.

trfMaybeLoc :: (a -> Trf (Maybe (b (Dom n) RangeStage))) -> SemanticInfo (Dom n) b -> Located a -> Trf (Maybe (Ann b (Dom n) RangeStage)) Source #

Transform a located part of the AST by automatically transforming the location. Sets the source range for transforming children.

trfAnnList :: SemanticInfo (Dom n) b ~ NoSemanticInfo => String -> (a -> Trf (b (Dom n) RangeStage)) -> [Located a] -> Trf (AnnList b (Dom n) RangeStage) Source #

Creates a place for a list of nodes with the default place at the end of the focus if the list is empty.

nonemptyAnnList :: [Ann e (Dom n) RangeStage] -> AnnList e (Dom n) RangeStage Source #

Creates a place for a list of nodes that cannot be empty.

makeJust :: Ann e (Dom n) RangeStage -> AnnMaybe e (Dom n) RangeStage Source #

Creates an optional node from an existing element

annLoc :: Trf (SemanticInfo (Dom n) b) -> Trf SrcSpan -> Trf (b (Dom n) RangeStage) -> Trf (Ann b (Dom n) RangeStage) Source #

Annotates a node with the given location and focuses on the given source span.

Focus manipulation

focusOn :: SrcSpan -> Trf a -> Trf a Source #

between :: AnnKeywordId -> AnnKeywordId -> Trf a -> Trf a Source #

Focuses the transformation to go between tokens. The tokens must be found inside the current range.

betweenIfPresent :: AnnKeywordId -> AnnKeywordId -> Trf a -> Trf a Source #

Focuses the transformation to go between tokens if they are present

focusAfter :: AnnKeywordId -> Trf a -> Trf a Source #

Focuses the transformation to be performed after the given token. The token must be found inside the current range.

focusBefore :: AnnKeywordId -> Trf a -> Trf a Source #

Focuses the transformation to be performed before the given token. The token must be found inside the current range.

before :: AnnKeywordId -> Trf SrcLoc Source #

Gets the position before the given token

after :: AnnKeywordId -> Trf SrcLoc Source #

Gets the position after the given token

annFrom :: AnnKeywordId -> Trf (SemanticInfo (Dom n) e) -> Trf (e (Dom n) RangeStage) -> Trf (Ann e (Dom n) RangeStage) Source #

The element should span from the given token to the end of focus

atTheStart :: Trf SrcLoc Source #

Gets the position at the beginning of the focus

atTheEnd :: Trf SrcLoc Source #

Gets the position at the end of the focus

tokenLoc :: AnnKeywordId -> Trf SrcSpan Source #

Searches for a token inside the focus and retrieves its location

tokenLocBack :: AnnKeywordId -> Trf SrcSpan Source #

Searches for a token backward inside the focus and retrieves its location

tokensLoc :: [AnnKeywordId] -> Trf SrcSpan Source #

Searches for tokens in the given order inside the parent element and returns their combined location

uniqueTokenAnywhere :: AnnKeywordId -> Trf SrcSpan Source #

Searches for a token and retrieves its location anywhere

annCont :: Trf (SemanticInfo (Dom n) e) -> Trf (e (Dom n) RangeStage) -> Trf (Ann e (Dom n) RangeStage) Source #

Annotates the given element with the current focus as a location.

copyAnnot :: SemanticInfo (Dom n) a ~ SemanticInfo (Dom n) b => (Ann a (Dom n) RangeStage -> b (Dom n) RangeStage) -> Trf (Ann a (Dom n) RangeStage) -> Trf (Ann b (Dom n) RangeStage) Source #

Annotates the element with the same annotation that is on the other element

foldLocs :: [SrcSpan] -> SrcSpan Source #

Combine source spans into one that contains them all

advanceStr :: String -> SrcLoc -> SrcLoc Source #

The location after the given string

updateCol :: (Int -> Int) -> SrcLoc -> SrcLoc Source #

Update column information in a source location

updateStart :: (SrcLoc -> SrcLoc) -> SrcSpan -> SrcSpan Source #

Update the start of the src span

updateEnd :: (SrcLoc -> SrcLoc) -> SrcSpan -> SrcSpan Source #

Update the end of the src span

collectLocs :: [Located e] -> SrcSpan Source #

Combine source spans of elements into one that contains them all

orderDefs :: [Ann e (Dom n) RangeStage] -> [Ann e (Dom n) RangeStage] Source #

Rearrange definitions to appear in the order they are defined in the source file.

orderAnnList :: AnnList e (Dom n) RangeStage -> AnnList e (Dom n) RangeStage Source #

Orders a list of elements to the order they are defined in the source file.

trfScopedSequence :: HsHasName d => (d -> Trf e) -> [d] -> Trf [e] Source #

Transform a list of definitions where the defined names are in scope for subsequent definitions

splitLocated :: Located String -> [Located String] Source #

Splits a given string at whitespaces while calculating the source location of the fragments