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

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.FromGHC

Contents

Description

The FromGHC module provides a way to transform the GHC AST into our AST. This transformation is done in the Ghc monad. The conversion can be performed from the Parsed and the Renamed GHC AST. If the renamed AST is given, additional semantic information is looked up while traversing the AST.

Synopsis

Documentation

addTypeInfos :: LHsBinds Id -> Ann Module (Dom Name) RangeStage -> Ghc (Ann Module IdDom RangeStage) Source #

createModuleInfo :: Module -> Trf (ModuleInfo Name) Source #

trfModule :: Module -> Located (HsModule RdrName) -> Trf (Ann Module (Dom RdrName) RangeStage) Source #

trfModuleRename :: Module -> Ann Module (Dom RdrName) RangeStage -> (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], Maybe LHsDocString) -> Located (HsModule RdrName) -> Trf (Ann Module (Dom Name) RangeStage) Source #

trfModuleHead :: TransformName n r => Maybe (Located ModuleName) -> Maybe (Located [LIE n]) -> Maybe (Located WarningTxt) -> Trf (AnnMaybe ModuleHead (Dom r) RangeStage) Source #

trfFilePragmas :: Trf (AnnList FilePragma (Dom r) RangeStage) Source #

trfLanguagePragma :: Located String -> Trf (Ann FilePragma (Dom r) RangeStage) Source #

trfOptionsPragma :: Located String -> Trf (Ann FilePragma (Dom r) RangeStage) Source #

trfModulePragma :: Maybe (Located WarningTxt) -> Trf (AnnMaybe ModulePragma (Dom r) RangeStage) Source #

trfText' :: StringLiteral -> Trf (StringNode (Dom r) RangeStage) Source #

trfExportList :: TransformName n r => SrcLoc -> Maybe (Located [LIE n]) -> Trf (AnnMaybe ExportSpecList (Dom r) RangeStage) Source #

trfExportList' :: TransformName n r => [LIE n] -> Trf (ExportSpecList (Dom r) RangeStage) Source #

trfExport :: TransformName n r => LIE n -> Trf (Maybe (Ann ExportSpec (Dom r) RangeStage)) Source #

trfImports :: TransformName n r => [LImportDecl n] -> Trf (AnnList ImportDecl (Dom r) RangeStage) Source #

trfImport :: TransformName n r => LImportDecl n -> Trf (Ann ImportDecl (Dom r) RangeStage) Source #

trfImportSpecs :: TransformName n r => Maybe (Bool, Located [LIE n]) -> Trf (AnnMaybe ImportSpec (Dom r) RangeStage) Source #

trfIESpec :: TransformName n r => LIE n -> Trf (Maybe (Ann IESpec (Dom r) RangeStage)) Source #

trfIESpec' :: TransformName n r => IE n -> Trf (Maybe (IESpec (Dom r) RangeStage)) Source #

type Trf = ReaderT TrfInput Ghc Source #

The transformation monad type

data TrfInput Source #

The (immutable) data for the transformation

Constructors

TrfInput 

Fields

define :: Trf a -> Trf a Source #

Perform the transformation taking names as defined.

defineTypeVars :: Trf a -> Trf a Source #

Perform the transformation taking type variable names as defined.

typeVarTransform :: Trf a -> Trf a Source #

Transform as type variables

transformingPossibleVar :: HsHasName n => n -> Trf a -> Trf a Source #

Transform a name as a type variable if it is one.

addToScope :: HsHasName e => e -> Trf a -> Trf a Source #

Perform the transformation putting the given definition in a new local scope.

addToCurrentScope :: HsHasName e => e -> Trf a -> Trf a Source #

Perform the transformation putting the given definitions in the current scope.

runTrf :: Map ApiAnnKey [SrcSpan] -> Map String [Located String] -> Trf a -> Ghc a Source #

Performs the transformation given the tokens of the source file

getOriginalName :: RdrName -> Trf String Source #

Get the original format of a name (before scoping).

trfOperator :: TransformName n r => Located n -> Trf (Ann Operator (Dom r) RangeStage) Source #

trfOperator' :: TransformName n r => n -> Trf (Operator (Dom r) RangeStage) Source #

trfName :: TransformName n r => Located n -> Trf (Ann Name (Dom r) RangeStage) Source #

trfName' :: TransformName n r => n -> Trf (Name (Dom r) RangeStage) Source #

trfAmbiguousFieldName :: TransformName n r => Located (AmbiguousFieldOcc n) -> Trf (Ann Name (Dom r) RangeStage) Source #

trfAmbiguousFieldName' :: forall n r. TransformName n r => SrcSpan -> AmbiguousFieldOcc n -> Trf (Ann Name (Dom r) RangeStage) Source #

class (TransformableName name, HsHasName name, TransformableName res, HsHasName res, GHCName res) => TransformName name res where Source #

This class allows us to use the same transformation code for multiple variants of the GHC AST. GHC Name annotated with name can be transformed to our representation with semantic annotations of res.

Minimal complete definition

transformName

Methods

transformName :: name -> res Source #

Demote a given name

Instances

((~) * n r, TransformableName n, HsHasName n) => TransformName n r Source # 

Methods

transformName :: n -> r Source #

(TransformableName res, GHCName res, HsHasName res) => TransformName Name res Source # 

Methods

transformName :: Name -> res Source #

trfSimpleName :: TransformName n r => Located n -> Trf (Ann SimpleName (Dom r) RangeStage) Source #

trfSimpleName' :: TransformName n r => n -> Trf (SimpleName (Dom r) RangeStage) Source #

trfNameStr :: String -> Trf (AnnList UnqualName (Dom r) RangeStage) Source #

Creates a qualified name from a name string

trfNameStr' :: String -> SrcLoc -> [Ann UnqualName (Dom r) RangeStage] Source #

trfModuleName :: Located ModuleName -> Trf (Ann ModuleName (Dom r) RangeStage) Source #

trfModuleName' :: ModuleName -> Trf (ModuleName (Dom r) RangeStage) Source #

trfFastString :: Located FastString -> Trf (Ann StringNode (Dom r) RangeStage) Source #

trfDataKeyword :: NewOrData -> Trf (Ann DataOrNewtypeKeyword (Dom r) RangeStage) Source #

trfCallConv :: Located CCallConv -> Trf (Ann CallConv (Dom r) RangeStage) Source #

trfCallConv' :: CCallConv -> Trf (CallConv (Dom r) RangeStage) Source #

trfSafety :: SrcSpan -> Located Safety -> Trf (AnnMaybe Safety (Dom r) RangeStage) Source #

trfOverlap :: Located OverlapMode -> Trf (Ann OverlapPragma (Dom r) RangeStage) Source #

trfRole :: Located (Maybe Role) -> Trf (Ann Role (Dom r) RangeStage) Source #

trfPhase :: Trf SrcLoc -> Activation -> Trf (AnnMaybe PhaseControl (Dom r) RangeStage) Source #

trfPhaseNum :: PhaseNum -> Trf (Ann PhaseNumber (Dom r) RangeStage) Source #

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

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 #

noSemaInfo :: src -> NodeInfo NoSemanticInfo src Source #

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

Creates a place for a missing node with a default location

emptyList :: String -> Trf SrcLoc -> Trf (AnnList e (Dom n) RangeStage) Source #

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.

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

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

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

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.

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

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

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

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.

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

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.

trfMaybeLocNoSema :: SemanticInfo (Dom n) b ~ NoSemanticInfo => (a -> Trf (Maybe (b (Dom n) RangeStage))) -> Located a -> Trf (Maybe (Ann b (Dom n) RangeStage)) Source #

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.

trfAnnList' :: String -> (Located a -> Trf (Ann b (Dom n) RangeStage)) -> [Located a] -> Trf (AnnList b (Dom n) RangeStage) Source #

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.

annLocNoSema :: SemanticInfo (Dom n) b ~ NoSemanticInfo => Trf SrcSpan -> Trf (b (Dom n) RangeStage) -> Trf (Ann b (Dom n) RangeStage) Source #

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 after 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.

annContNoSema :: SemanticInfo (Dom n) e ~ NoSemanticInfo => Trf (e (Dom n) RangeStage) -> Trf (Ann e (Dom n) RangeStage) Source #

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

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