Safe Haskell | None |
---|
This module contains a collection of program analysis and transformation functions (the API) that work over the Type Decorated AST. Most of the functions defined in the module are taken directly from the API, but in some cases are modified to work with the type decorated AST.
In particular some new functions have been added to make type decorated AST traversals easier.
In HaRe, in order to preserve the comments and layout of refactored programs, a refactoring modifies not only the AST but also the token stream, and the program source after the refactoring is extracted from the token stream rather than the AST, for the comments and layout information is kept in the token steam instead of the AST. As a consequence, a program transformation function from this API modifies both the AST and the token stream (unless explicitly stated). So when you build your own program transformations, try to use the API to do the transformation, as this can liberate you from caring about the token stream.
This type decorated API is still in development. Any suggestions and comments are very much welcome.
- inScopeInfo :: InScopes -> [(String, NameSpace, ModuleName, Maybe ModuleName)]
- isInScopeAndUnqualified :: String -> InScopes -> Bool
- isInScopeAndUnqualifiedGhc :: String -> Maybe Name -> RefactGhc Bool
- inScopeNames :: String -> RefactGhc [Name]
- isExported :: Name -> RefactGhc Bool
- isExplicitlyExported :: Name -> RenamedSource -> Bool
- modIsExported :: ModuleName -> RenamedSource -> Bool
- isFieldName :: Name -> Bool
- isClassName :: Name -> Bool
- isInstanceName :: Name -> Bool
- hsPNs :: Data t => t -> [PName]
- hsBinds :: HsValBinds t => t -> [LHsBind Name]
- replaceBinds :: HsValBinds t => t -> [LHsBind Name] -> t
- class Data t => HsValBinds t where
- hsValBinds :: t -> HsValBinds Name
- replaceValBinds :: t -> HsValBinds Name -> t
- hsTyDecls :: t -> [[LTyClDecl Name]]
- isDeclaredIn :: HsValBinds t => Name -> t -> Bool
- hsFreeAndDeclaredPNsOld :: Data t => t -> ([Name], [Name])
- hsFreeAndDeclaredNameStrings :: (Data t, Outputable t) => t -> RefactGhc ([String], [String])
- hsFreeAndDeclaredPNs :: (Data t, Outputable t) => t -> RefactGhc ([Name], [Name])
- hsFreeAndDeclaredGhc :: (Data t, Outputable t) => t -> RefactGhc (FreeNames, DeclaredNames)
- getDeclaredTypes :: LTyClDecl Name -> [Name]
- getFvs :: [LHsBind Name] -> [([Name], NameSet)]
- getFreeVars :: [LHsBind Name] -> [Name]
- getDeclaredVars :: [LHsBind Name] -> [Name]
- hsVisiblePNs :: (FindEntity e, Data e, Data t, HsValBinds t, Outputable e) => e -> t -> RefactGhc [Name]
- hsVisibleNames :: (FindEntity t1, Data t1, Data t2, HsValBinds t2, Outputable t1) => t1 -> t2 -> RefactGhc [String]
- hsFDsFromInside :: Data t => t -> RefactGhc ([Name], [Name])
- hsFDNamesFromInside :: Data t => t -> RefactGhc ([String], [String])
- hsVisibleDs :: (FindEntity e, Data e, Data t, HsValBinds t, Outputable e) => e -> t -> RefactGhc DeclaredNames
- isVarId :: String -> Bool
- isConId :: String -> Bool
- isOperator :: String -> Bool
- isTopLevelPN :: Name -> RefactGhc Bool
- isLocalPN :: Name -> Bool
- isNonLibraryName :: Name -> Bool
- isQualifiedPN :: Name -> RefactGhc Bool
- isFunOrPatName :: Data t => Name -> t -> Bool
- isTypeSig :: Located (Sig a) -> Bool
- isFunBindP :: HsDeclP -> Bool
- isFunBindR :: LHsBind t -> Bool
- isPatBindP :: HsDeclP -> Bool
- isPatBindR :: LHsBind t -> Bool
- isSimplePatBind :: Data t => LHsBind t -> Bool
- isComplexPatBind :: LHsBind Name -> Bool
- isFunOrPatBindP :: HsDeclP -> Bool
- isFunOrPatBindR :: LHsBind t -> Bool
- usedWithoutQualR :: Data t => Name -> t -> Bool
- isUsedInRhs :: Data t => Located Name -> t -> Bool
- findPNT :: Data t => Located Name -> t -> Bool
- findPN :: Data t => Name -> t -> Bool
- findAllNameOccurences :: Data t => Name -> t -> [Located Name]
- findPNs :: Data t => [Name] -> t -> Bool
- findEntity :: (FindEntity a, Data b, Typeable b) => a -> b -> Bool
- findEntity' :: (Data a, Data b) => a -> b -> Maybe (SimpPos, SimpPos)
- sameOccurrence :: Located t -> Located t -> Bool
- defines :: Name -> LHsBind Name -> Bool
- definesP :: PName -> HsDeclP -> Bool
- definesTypeSig :: Name -> LSig Name -> Bool
- sameBind :: LHsBind Name -> LHsBind Name -> Bool
- class Data t => UsedByRhs t where
- isMainModule :: Module -> Bool
- getModule :: RefactGhc Module
- defineLoc :: Located Name -> SrcLoc
- useLoc :: Located Name -> SrcLoc
- locToExp :: (Data t, Typeable n) => SimpPos -> SimpPos -> t -> Maybe (Located (HsExpr n))
- locToName :: Data t => SimpPos -> t -> Maybe (Located Name)
- locToRdrName :: Data t => SimpPos -> t -> Maybe (Located RdrName)
- getName :: Data t => String -> t -> Maybe Name
- addDecl :: (Data t, HsValBinds t) => t -> Maybe Name -> (LHsBind Name, [LSig Name], Maybe [PosToken]) -> Bool -> RefactGhc t
- addItemsToImport :: ModuleName -> RenamedSource -> [Name] -> RefactGhc RenamedSource
- addHiding :: ModuleName -> RenamedSource -> [Name] -> RefactGhc RenamedSource
- addParamsToDecls :: [LHsBind Name] -> Name -> [Name] -> Bool -> RefactGhc [LHsBind Name]
- addActualParamsToRhs :: (Typeable t, Data t) => Bool -> Name -> [Name] -> t -> RefactGhc t
- addImportDecl :: RenamedSource -> ModuleName -> Maybe FastString -> Bool -> Bool -> Bool -> Maybe String -> Bool -> [Name] -> RefactGhc RenamedSource
- duplicateDecl :: Data t => [LHsBind Name] -> t -> Name -> Name -> RefactGhc [LHsBind Name]
- rmDecl :: Data t => Name -> Bool -> t -> RefactGhc (t, LHsBind Name, Maybe (LSig Name))
- rmTypeSig :: Data t => Name -> t -> RefactGhc (t, Maybe (LSig Name))
- rmTypeSigs :: Data t => [Name] -> t -> RefactGhc (t, [LSig Name])
- rmQualifier :: Data t => [Name] -> t -> RefactGhc t
- qualifyToplevelName :: Name -> RefactGhc ()
- renamePN :: Data t => Name -> Name -> Bool -> Bool -> t -> RefactGhc t
- autoRenameLocalVar :: HsValBinds t => Bool -> Name -> t -> RefactGhc t
- showEntities :: (t -> String) -> [t] -> String
- showPNwithLoc :: Located Name -> String
- defaultPN :: PName
- defaultName :: Name
- defaultExp :: HsExpP
- ghcToPN :: RdrName -> PName
- lghcToPN :: Located RdrName -> PName
- expToName :: Located (HsExpr Name) -> Name
- nameToString :: Name -> String
- patToPNT :: LPat Name -> Maybe Name
- pNtoPat :: Name -> Pat Name
- definedPNs :: LHsBind Name -> [Name]
- definingDeclsNames :: [Name] -> [LHsBind Name] -> Bool -> Bool -> [LHsBind Name]
- definingDeclsNames' :: Data t => [Name] -> t -> [LHsBind Name]
- definingSigsNames :: Data t => [Name] -> t -> [LSig Name]
- allNames :: Data t => t -> [Located Name]
- mkRdrName :: String -> RdrName
- mkNewGhcName :: Maybe Module -> String -> RefactGhc Name
- mkNewName :: String -> [String] -> Int -> String
- mkNewToplevelName :: Module -> String -> SrcSpan -> RefactGhc Name
- causeNameClashInExports :: Name -> Name -> ModuleName -> RenamedSource -> Bool
- prettyprint :: Outputable a => a -> String
- prettyprint2 :: Outputable a => a -> String
- removeOffset :: Int -> [PosToken] -> [PosToken]
- getDeclAndToks :: HsValBinds t => Name -> Bool -> [PosToken] -> t -> ([LHsBind Name], [PosToken])
- getSigAndToks :: Data t => Name -> t -> [PosToken] -> Maybe (LSig Name, [PosToken])
- getToksForDecl :: Data t => t -> [PosToken] -> [PosToken]
- removeToksOffset :: [PosToken] -> [PosToken]
- getParsedForRenamedLPat :: ParsedSource -> LPat Name -> LPat RdrName
- getParsedForRenamedName :: ParsedSource -> Located Name -> Located RdrName
- getParsedForRenamedLocated :: Typeable b => Located a -> RefactGhc (Located b)
- newNameTok :: Bool -> SrcSpan -> Name -> PosToken
- stripLeadingSpaces :: [String] -> [String]
Program Analysis
Imports and exports
:: InScopes | The inscope relation . |
-> [(String, NameSpace, ModuleName, Maybe ModuleName)] | The result |
Process the inscope relation returned from the parsing and module analysis pass, and return a list of four-element tuples. Each tuple contains an identifier name, the identifier's namespace info, the identifier's defining module name and its qualifier name.
The same identifier may have multiple entries in the result because it may have different qualifiers. This makes it easier to decide whether the identifier can be used unqualifiedly by just checking whether there is an entry for it with the qualifier field being Nothing.
Return True if the identifier is inscope and can be used without a qualifier.
isInScopeAndUnqualifiedGhcSource
:: String | The identifier name. |
-> Maybe Name | Existing name, to be excluded from test, if known |
-> RefactGhc Bool | The result. |
Return True if the identifier is inscope and can be used without a qualifier. The identifier name string may have a qualifier already NOTE: may require qualification based on name clash with an existing identifier.
isExported :: Name -> RefactGhc BoolSource
Return True if an identifier is exported by the module currently being refactored.
:: Name | The identifier |
-> RenamedSource | The AST of the module |
-> Bool | The result |
Return True if an identifier is explicitly exported by the module.
:: ModuleName | The module name |
-> RenamedSource | The AST of the module |
-> Bool | The result |
Return True if the current module is exported either by default or by specifying the module name in the export.
Variable analysis
isFieldName :: Name -> BoolSource
True if the name is a field name
isClassName :: Name -> BoolSource
True if the name is a field name
isInstanceName :: Name -> BoolSource
True if the name is a class instance
hsPNs :: Data t => t -> [PName]Source
Collect the identifiers (in PName format) in a given syntax phrase.
hsBinds :: HsValBinds t => t -> [LHsBind Name]Source
replaceBinds :: HsValBinds t => t -> [LHsBind Name] -> tSource
class Data t => HsValBinds t whereSource
hsValBinds :: t -> HsValBinds NameSource
Return the binds that are directly enclosed in the given syntax phrase. hsValBinds :: t -> [GHC.LHsBind GHC.Name]
replaceValBinds :: t -> HsValBinds Name -> tSource
Replace the directly enclosed bind list by the given bind list. Note: This function does not modify the token stream. replaceBinds :: t -> [GHC.LHsBind GHC.Name] -> t
hsTyDecls :: t -> [[LTyClDecl Name]]Source
Return True if the specified identifier is declared in the given syntax phrase. isDeclaredIn :: GHC.Name -> t -> Bool
Return the type class definitions that are directly enclosed in the given syntax phrase. Note: only makes sense for GHC.RenamedSource
isDeclaredIn :: HsValBinds t => Name -> t -> BoolSource
hsFreeAndDeclaredPNsOld :: Data t => t -> ([Name], [Name])Source
Collect the free and declared variables (in the GHC.Name format) in a given syntax phrase t. In the result, the first list contains the free variables, and the second list contains the declared variables. Expects RenamedSource
hsFreeAndDeclaredNameStrings :: (Data t, Outputable t) => t -> RefactGhc ([String], [String])Source
The same as hsFreeAndDeclaredPNs
except that the returned
variables are in the String format.
hsFreeAndDeclaredPNs :: (Data t, Outputable t) => t -> RefactGhc ([Name], [Name])Source
hsFreeAndDeclaredGhc :: (Data t, Outputable t) => t -> RefactGhc (FreeNames, DeclaredNames)Source
Collect the free and declared variables (in the GHC.Name format) in a given syntax phrase t. In the result, the first list contains the free variables, and the second list contains the declared variables. TODO: use GHC.NameSet instead of lists for FreeNames/DeclaredNames NOTE: The GHC fvs fields only carry non-GHC values, as they are used in the renaming process
getDeclaredTypes :: LTyClDecl Name -> [Name]Source
getFreeVars :: [LHsBind Name] -> [Name]Source
getDeclaredVars :: [LHsBind Name] -> [Name]Source
hsVisiblePNs :: (FindEntity e, Data e, Data t, HsValBinds t, Outputable e) => e -> t -> RefactGhc [Name]Source
Given syntax phrases e and t, if e occurs in t, then return those variables which are declared in t and accessible to e, otherwise return [].
hsVisibleNames :: (FindEntity t1, Data t1, Data t2, HsValBinds t2, Outputable t1) => t1 -> t2 -> RefactGhc [String]Source
Same as hsVisiblePNs
except that the returned identifiers are
in String format.
hsFDsFromInside :: Data t => t -> RefactGhc ([Name], [Name])Source
hsFDsFromInside
is different from hsFreeAndDeclaredPNs
in
that: given an syntax phrase t, hsFDsFromInside
returns not only
the declared variables that are visible from outside of t, but also
those declared variables that are visible to the main expression
inside t.
NOTE: Expects to be given RenamedSource
hsFDNamesFromInside :: Data t => t -> RefactGhc ([String], [String])Source
The same as hsFDsFromInside
except that the returned variables
are in the String format
hsVisibleDs :: (FindEntity e, Data e, Data t, HsValBinds t, Outputable e) => e -> t -> RefactGhc DeclaredNamesSource
Given syntax phrases e and t, if e occurs in t, then return those variables which are declared in t and accessible to e, otherwise return [].
Property checking
isOperator :: String -> BoolSource
Return True if a string is a lexically valid operator name.
isTopLevelPN :: Name -> RefactGhc BoolSource
Return True if a PName is a toplevel PName.
isNonLibraryName :: Name -> BoolSource
Return True if the name has a GHC.SrcSpan
, i.e. is declared in
source we care about
isQualifiedPN :: Name -> RefactGhc BoolSource
Return True if a PName is a qualified PName. AZ:NOTE: this tests the use instance, the underlying name may be qualified. e.g. used name is zip, GHC.List.zip NOTE2: not sure if this gives a meaningful result for a GHC.Name
isFunOrPatName :: Data t => Name -> t -> BoolSource
Return True if a PName is a function/pattern name defined in t.
isTypeSig :: Located (Sig a) -> BoolSource
Return True if a declaration is a type signature declaration. isTypeSig ::HsDeclP->Bool isTypeSig (TiDecorate.Dec (HsTypeSig loc is c tp))=True
isFunBindP :: HsDeclP -> BoolSource
Return True if a declaration is a function definition.
isFunBindR :: LHsBind t -> BoolSource
isPatBindP :: HsDeclP -> BoolSource
Returns True if a declaration is a pattern binding.
isPatBindR :: LHsBind t -> BoolSource
isSimplePatBind :: Data t => LHsBind t -> BoolSource
Return True if a declaration is a pattern binding which only defines a variable value.
isComplexPatBind :: LHsBind Name -> BoolSource
Return True if a declaration is a pattern binding but not a simple one.
isFunOrPatBindP :: HsDeclP -> BoolSource
Return True if a declaration is a function/pattern definition.
isFunOrPatBindR :: LHsBind t -> BoolSource
Return True if a declaration is a function/pattern definition.
usedWithoutQualR :: Data t => Name -> t -> BoolSource
Return True if the identifier is unqualifiedly used in the given syntax phrase. usedWithoutQualR :: GHC.Name -> GHC.ParsedSource -> Bool
isUsedInRhs :: Data t => Located Name -> t -> BoolSource
Return True if the identifier is used in the RHS if a function/pattern binding.
findPNT :: Data t => Located Name -> t -> BoolSource
Return True if the identifier occurs in the given syntax phrase.
findPN :: Data t => Name -> t -> BoolSource
Return True if the identifier occurs in the given syntax phrase.
findAllNameOccurences :: Data t => Name -> t -> [Located Name]Source
Find all occurrences with location of the given name
findPNs :: Data t => [Name] -> t -> BoolSource
Return True if any of the specified PNames ocuur in the given syntax phrase.
findEntity :: (FindEntity a, Data b, Typeable b) => a -> b -> BoolSource
Returns True is a syntax phrase, say a, is part of another syntax phrase, say b. NOTE: very important: only do a shallow check
sameOccurrence :: Located t -> Located t -> BoolSource
Return True if syntax phrases t1 and t2 refer to the same one.
defines :: Name -> LHsBind Name -> BoolSource
Return True if the function/pattern binding defines the specified identifier.
definesTypeSig :: Name -> LSig Name -> BoolSource
Return True if the declaration defines the type signature of the specified identifier.
Modules and files
isMainModule :: Module -> BoolSource
Locations
defineLoc :: Located Name -> SrcLocSource
Return the identifier's defining location. defineLoc::PNT->SrcLoc
:: (Data t, Typeable n) | |
=> SimpPos | The start position. |
-> SimpPos | The end position. |
-> t | The syntax phrase. |
-> Maybe (Located (HsExpr n)) | The result. |
Given the syntax phrase, find the largest-leftmost expression contained in the region specified by the start and end position, if found.
:: Data t | |
=> SimpPos | The row and column number |
-> t | The syntax phrase |
-> Maybe (Located Name) | The result |
Find the identifier(in GHC.Name format) whose start position is
(row,col) in the file specified by the fileName, and returns
Nothing
if such an identifier does not exist.
:: Data t | |
=> SimpPos | The row and column number |
-> t | The syntax phrase |
-> Maybe (Located RdrName) | The result |
Find the identifier(in GHC.RdrName format) whose start position is
(row,col) in the file specified by the fileName, and returns
Nothing
if such an identifier does not exist.
Find the identifier with the given name. This looks through the given syntax phrase for the first GHC.Name which matches. Because it is Renamed source, the GHC.Name will include its defining location. Returns Nothing if the name is not found.
Program transformation
Adding
:: (Data t, HsValBinds t) | |
=> t | The AST to be updated |
-> Maybe Name | If this is Just, then the declaration will be added right after this identifier's definition. |
-> (LHsBind Name, [LSig Name], Maybe [PosToken]) | The declaration with optional signatures to be added, in both AST and Token stream format (optional). If signature and tokens provided, the tokens should include the signature too |
-> Bool | True means the declaration is a toplevel declaration. |
-> RefactGhc t |
Adding a declaration to the declaration list of the given syntax phrase. If the second argument is Nothing, then the declaration will be added to the beginning of the declaration list, but after the data type declarations is there is any.
:: ModuleName | The imported module name |
-> RenamedSource | The current module |
-> [Name] | The items to be added ->Maybe GHC.Name -- ^ The condition identifier. |
-> RefactGhc RenamedSource | The result (with token stream updated) |
Add identifiers (given by the third argument) to the explicit entity list in the declaration importing the specified module name. This function does nothing if the import declaration does not have an explicit entity list.
:: ModuleName | The imported module name |
-> RenamedSource | The current module |
-> [Name] | The items to be added |
-> RefactGhc RenamedSource | The result (with token stream updated) |
add items to the hiding list of an import declaration which imports the specified module.
:: RenamedSource | |
-> ModuleName | |
-> Maybe FastString | qualifier |
-> Bool | |
-> Bool | |
-> Bool | |
-> Maybe String | alias |
-> Bool | |
-> [Name] | |
-> RefactGhc RenamedSource |
Add identifiers to the export list of a module. If the second argument is like: Just p, then do the adding only if p occurs in the export list, and the new identifiers are added right after p in the export list. Otherwise the new identifiers are add to the beginning of the export list. In the case that the export list is emport, then if the third argument is True, then create an explict export list to contain only the new identifiers, otherwise do nothing.
:: Data t | |
=> [LHsBind Name] | The declaration list |
-> t | Any signatures are in here |
-> Name | The identifier whose definition is to be duplicated |
-> Name | The new name (possibly qualified) |
-> RefactGhc [LHsBind Name] | The result |
Remove those specified items from the entity list in the import declaration.
Remove the specified entities from the module's exports. The entities can be specified in either of two formats: i.e. either specify the module names and identifier names to be removed, so just given the exact AST for these entities.
Duplicate a function/pattern binding declaration under a new name right after the original one. Also updates the token stream.
Removing
:: Data t | |
=> Name | The identifier whose definition is to be removed. |
-> Bool | True means including the type signature. |
-> t | The declaration list. |
-> RefactGhc (t, LHsBind Name, Maybe (LSig Name)) | The result and the removed declaration, with SrcSpans adjusted to reflect the stashed tokens and the possibly removed siganture |
Remove the declaration (and the type signature is the second parameter is True) that defines the given identifier from the declaration list.
:: Data t | |
=> Name | The identifier whose type signature is to be removed. |
-> t | The declarations |
-> RefactGhc (t, Maybe (LSig Name)) | The result and removed signature, if there was one |
Remove the type signature that defines the given identifier's type from the declaration list.
:: Data t | |
=> [Name] | The identifiers whose type signatures are to be removed. |
-> t | The declarations |
-> RefactGhc (t, [LSig Name]) | The result and removed signatures, if there were any |
Remove multiple type signatures
Updating
Remove the qualifier from the given identifiers in the given syntax phrase.
qualifyToplevelName :: Name -> RefactGhc ()Source
Replace all occurences of a top level GHC.Name with a qualified version.
:: Data t | |
=> Name | The identifier to be renamed. |
-> Name | The new name, including possible qualifier |
-> Bool | True means modifying the token stream as well. |
-> Bool | True means use the qualified form for the new name. |
-> t | The syntax phrase |
-> RefactGhc t |
Rename each occurrences of the identifier in the given syntax phrase with the new name. If the Bool parameter is True, then modify both the AST and the token stream, otherwise only modify the AST. TODO: the syntax phrase is required to be GHC.Located, not sure how to specify this without breaking the everywhereMStaged call
:: HsValBinds t | |
=> Bool | True means modfiying the token stream as well. |
-> Name | The identifier. |
-> t | The syntax phrase. |
-> RefactGhc t | The result. |
Check whether the specified identifier is declared in the given syntax phrase t, if so, rename the identifier by creating a new name automatically. If the Bool parameter is True, the token stream will be modified, otherwise only the AST is modified.
Miscellous
Parsing, writing and showing
showEntities :: (t -> String) -> [t] -> StringSource
Show a list of entities, the parameter f is a function that specifies how to format an entity.
showPNwithLoc :: Located Name -> StringSource
Show a PName in a format like: pn
(at row:r, col: c).
Locations
Default values
Default expression.
Identifiers, expressions, patterns and declarations
expToName :: Located (HsExpr Name) -> NameSource
If an expression consists of only one identifier then return this identifier in the GHC.Name format, otherwise return the default Name
nameToString :: Name -> StringSource
patToPNT :: LPat Name -> Maybe NameSource
If a pattern consists of only one identifier then return this identifier, otherwise return Nothing
definedPNs :: LHsBind Name -> [Name]Source
Return the list of identifiers (in PName format) defined by a function/pattern binding.
:: [Name] | The specified identifiers. |
-> [LHsBind Name] | A collection of declarations. |
-> Bool | True means to include the type signature. |
-> Bool | True means to look at the local declarations as well. |
-> [LHsBind Name] | The result. |
Find those declarations(function/pattern binding) which define the specified GHC.Names. incTypeSig indicates whether the corresponding type signature will be included.
:: Data t | |
=> [Name] | The specified identifiers. |
-> t | A collection of declarations. |
-> [LHsBind Name] | The result. |
Find those declarations(function/pattern binding) which define the specified GHC.Names. incTypeSig indicates whether the corresponding type signature will be included.
:: Data t | |
=> [Name] | The specified identifiers. |
-> t | A collection of declarations. |
-> [LSig Name] | The result. |
Find those type signatures for the specified GHC.Names.
Find all Located Names in the given Syntax phrase.
Others
mkNewGhcName :: Maybe Module -> String -> RefactGhc NameSource
Make a new GHC.Name, using the Unique Int sequence stored in the RefactState.
:: String | The old name |
-> [String] | The set of names which the new name cannot take |
-> Int | The posfix value |
-> String | The result |
Create a new name base on the old name. Suppose the old name is f
, then
the new name would be like f_i
where i
is an integer.
:: Name | The original name |
-> Name | The new name |
-> ModuleName | The identity of the module |
-> RenamedSource | The AST of the module |
-> Bool | The result |
Check if the proposed new name will conflict with an existing export
prettyprint :: Outputable a => a -> StringSource
prettyprint2 :: Outputable a => a -> StringSource
removeOffset :: Int -> [PosToken] -> [PosToken]Source
Remove at most offset
whitespaces from each line in the tokens
Typed AST traversals (added by CMB)
Miscellous
Debug stuff
getDeclAndToks :: HsValBinds t => Name -> Bool -> [PosToken] -> t -> ([LHsBind Name], [PosToken])Source
getSigAndToks :: Data t => Name -> t -> [PosToken] -> Maybe (LSig Name, [PosToken])Source
Get the signature and tokens for a declaration
getToksForDecl :: Data t => t -> [PosToken] -> [PosToken]Source
removeToksOffset :: [PosToken] -> [PosToken]Source
Normalise a set of tokens to start at the offset of the first one
getParsedForRenamedLPat :: ParsedSource -> LPat Name -> LPat RdrNameSource
Given a RenamedSource LPAT, return the equivalent ParsedSource part. NOTE: returns pristine ParsedSource, since HaRe does not change it
getParsedForRenamedName :: ParsedSource -> Located Name -> Located RdrNameSource
Given a RenamedSource Located name, return the equivalent ParsedSource part. NOTE: returns pristine ParsedSource, since HaRe does not change it
getParsedForRenamedLocated :: Typeable b => Located a -> RefactGhc (Located b)Source
Given a RenamedSource Located name, return the equivalent ParsedSource part. NOTE: returns pristine ParsedSource, since HaRe does not change it
newNameTok :: Bool -> SrcSpan -> Name -> PosTokenSource
Create a new name token. If useQual
then use the qualified
name, if it exists.
The end position is not changed, so the eventual realignment can
know what the difference in length in the token is
stripLeadingSpaces :: [String] -> [String]Source
Take a list of strings and return a list with the longest prefix of spaces removed