HaRe-0.8.0.0: the Haskell Refactorer.

Safe HaskellNone
LanguageHaskell98

Language.Haskell.Refact.API

Contents

Description

This module should provide all that is required to write further refactorings. NOTE: it is currently unstable, and may change without notice on minor version number bumps

Synopsis

from Monad

type ParseResult = TypecheckedModule Source

Result of parsing a Haskell source file. It is simply the TypeCheckedModule produced by GHC.

type TargetModule = ModulePath Source

data RefactFlags Source

Constructors

RefFlags 

Fields

rsDone :: !Bool

Current traversal has already made a change

data StateStorage Source

Provide some temporary storage while the refactoring is taking place

The GHC Monad

from Utils

Managing the GHC / project environment

parseSourceFileGhc :: FilePath -> RefactGhc () Source

Parse a single source file into a GHC session

The bits that do the work

runRefacSession Source

Arguments

:: RefactSettings 
-> Options

ghc-mod options

-> RefactGhc [ApplyRefacResult]

The computation doing the refactoring. Normally created via applyRefac

-> IO [FilePath] 

Manage a whole refactor session. Initialise the monad, load the whole project if required, and then apply the individual refactorings, and write out the resulting files.

It is intended that this forms the umbrella function, in which applyRefac is called

applyRefac Source

Arguments

:: RefactGhc a

The refactoring

-> RefacSource

where to get the module and toks

-> RefactGhc (ApplyRefacResult, a) 

Apply a refactoring (or part of a refactoring) to a single module

refactDone :: [ApplyRefacResult] -> Bool Source

Returns True if any of the results has its modified flag set

type ApplyRefacResult = ((FilePath, RefacResult), (Anns, ParsedSource)) Source

The result of a refactoring is the file, a flag as to whether it was modified, and the updated AST

nameSybQuery :: (Typeable a, Typeable t) => (Located a -> Maybe r) -> t -> Maybe r Source

getModuleName :: ParsedSource -> Maybe (ModuleName, String) Source

Extract the module name from the parsed source, if there is one

clientModsAndFiles :: ModulePath -> RefactGhc [TargetModule] Source

Return the client modules and file names. The client modules of module, say m, are those modules which directly or indirectly import module m.

serverModsAndFiles :: GhcMonad m => ModuleName -> m [ModSummary] Source

Return the server module and file names. The server modules of module, say m, are those modules which are directly or indirectly imported by module m. This can only be called in a live GHC session TODO: make sure this works with multiple targets. Is that needed? No?

from MonadFunctions

Conveniences for state access

New ghc-exactprint interfacing

liftT :: HasTransform m => forall a. Transform a -> m a

State flags for managing generic traversals

from LocUtils

type SimpPos = (Int, Int) Source

getGhcLoc :: SrcSpan -> (Int, Int) Source

gets the (row,col) of the start of the GHC.SrcSpan, or (-1,-1) if there is an GHC.UnhelpfulSpan

getGhcLocEnd :: SrcSpan -> (Int, Int) Source

gets the (row,col) of the end of the GHC.SrcSpan, or (-1,-1) if there is an GHC.UnhelpfulSpan

emptyList :: [t] -> Bool Source

Get around lack of instance Eq when simply testing for empty list TODO: get rid of this in favour of null built in fn

from TypeSyn

ghead :: String -> [a] -> a

glast :: String -> [a] -> a

gtail :: String -> [a] -> [a]

gfromJust :: String -> Maybe a -> a

from TypeUtils

Program Analysis

Imports and exports

inScopeInfo Source

Arguments

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

isInScopeAndUnqualified Source

Arguments

:: String

The identifier name.

-> InScopes

The inscope relation

-> Bool

The result.

Return True if the identifier is inscope and can be used without a qualifier.

isInScopeAndUnqualifiedGhc Source

Arguments

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

inScopeNames Source

Arguments

:: String

The identifier name.

-> RefactGhc [Name]

The result.

Return all Names that correspond to the given string, in the current module.

isExported :: Name -> RefactGhc Bool Source

Return True if an identifier is exported by the module currently being refactored.

isExplicitlyExported Source

Arguments

:: Name

The identifier

-> RenamedSource

The AST of the module

-> Bool

The result

Return True if an identifier is explicitly exported by the module.

modIsExported Source

Arguments

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

equivalentNameInNewMod :: Name -> RefactGhc [Name] Source

Given a Name defined in one module, find the equivalent one in the currently loaded module. This is required otherwise name equality checking based on nameUnique will fail.

Variable analysis

isFieldName :: Name -> Bool Source

True if the name is a field name

isClassName :: Name -> Bool Source

True if the name is a field name

isInstanceName :: Name -> Bool Source

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 name => t -> [LHsBind name] Source

class (Data t, Data name) => HsValBinds t name | t -> name where Source

Methods

hsValBinds :: t -> HsValBinds name Source

Return the binds that are directly enclosed in the given syntax phrase. hsValBinds :: t -> [GHC.LHsBind GHC.Name]

hsTyDecls :: t -> [[LTyClDecl name]] Source

Return the type class definitions that are directly enclosed in the given syntax phrase. Note: only makes sense for GHC.RenamedSource

Instances

HsValBinds ParsedSource RdrName Source 
HsValBinds RenamedSource Name Source 
HsValBinds Name Name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [[LTyClDecl name]] name Source 
(DataId name, Data name) => HsValBinds [LMatch name (LHsExpr name)] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LGRHS name (LHsExpr name)] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LStmt name (LHsExpr name)] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LTyClDecl name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [TyClGroup name] name Source 
(DataId name, Data name) => HsValBinds [LTyFamInstEqn name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LTyFamInstDecl name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LDataFamInstDecl name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LInstDecl name] name Source 
(DataId name, Data name) => HsValBinds [LHsBind name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LSig name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LHsType name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [SyntaxExpr name] name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds [LPat name] name Source 
(DataId name, Data name) => HsValBinds (HsGroup name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LTyClDecl name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (TyClGroup name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (HsDataDefn name) name Source 
(DataId name, Data name) => HsValBinds (LTyFamInstEqn name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (HsTyPats name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LInstDecl name) name Source 
(DataId name, Data name) => HsValBinds (HsLocalBinds name) name Source 
(DataId name, Data name) => HsValBinds (HsValBinds name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LHsBind name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LHsBinds name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (HsBind name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (HsIPBinds name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LSig name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LHsType name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (HsExpr name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LHsExpr name) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LPat name) name Source 
(DataId name, Data name) => HsValBinds (LMatch name (LHsExpr name)) name Source 
(DataId name, Data name) => HsValBinds (Match name (LHsExpr name)) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LGRHS name (LHsExpr name)) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (LStmt name (LHsExpr name)) name Source 
(OutputableBndr name, DataId name, Data name) => HsValBinds (Stmt name (LHsExpr name)) name Source 
(DataId name, Data name) => HsValBinds (MatchGroup name (LHsExpr name)) name Source 
(DataId name, Data name) => HsValBinds (GRHSs name (LHsExpr name)) name Source 

data FreeNames Source

For free variables

Constructors

FN 

Fields

fn :: [Name]
 

data DeclaredNames Source

For declared variables

Constructors

DN 

Fields

dn :: [Name]
 

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.

hsFreeAndDeclaredRdr :: Data t => NameMap -> t -> (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. Expects RenamedSource

hsFreeAndDeclaredGhc :: Data 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 hsFreeAndDeclaredGhc :: (SYB.Data t,GHC.Outputable t)

getDeclaredTypes :: LTyClDecl Name -> [Name] Source

Get the names of all types declared in the given declaration

getFvs :: [LHsBind Name] -> [([Name], NameSet)] Source

Experiment with GHC fvs stuff

hsVisiblePNs :: (FindEntity e, HsValBinds t Name, 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 [].

hsVisiblePNsRdr :: (FindEntity e, Data t, Outputable e) => NameMap -> 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, HsValBinds t2 Name, Outputable t1) => t1 -> t2 -> RefactGhc [String] Source

Same as hsVisiblePNs except that the returned identifiers are in String format.

hsVisibleNamesRdr :: (FindEntity t1, Data t2, Outputable t1) => t1 -> t2 -> RefactGhc [String] Source

Same as hsVisiblePNs except that the returned identifiers are in String format.

hsFDsFromInsideRdr :: Data t => NameMap -> t -> RefactGhc (FreeNames, DeclaredNames) Source

hsFDsFromInsideRdr is different from hsFreeAndDeclaredPNs in that: given an syntax phrase t, hsFDsFromInsideRdr 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

hsFDNamesFromInsideRdr :: Data t => t -> RefactGhc ([String], [String]) Source

The same as hsFDsFromInside except that the returned variables are in the 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, Outputable e, Data t, HsValBinds t Name) => e -> t -> RefactGhc DeclaredNames 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 [].

Property checking

isVarId :: String -> Bool Source

Return True if a string is a lexically valid variable name.

isConId :: String -> Bool Source

Return True if a string is a lexically valid constructor name.

isOperator :: String -> Bool Source

Return True if a string is a lexically valid operator name.

isTopLevelPN :: Name -> RefactGhc Bool Source

Return True if a PName is a toplevel PName.

isLocalPN :: Name -> Bool Source

Return True if a PName is a local PName.

isNonLibraryName :: Name -> Bool Source

Return True if the name has a GHC.SrcSpan, i.e. is declared in source we care about

isQualifiedPN :: Name -> RefactGhc Bool Source

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 -> Bool Source

Return True if a PName is a function/pattern name defined in t.

isTypeSig :: LSig a -> Bool Source

Return True if a declaration is a type signature declaration.

isFunBindP :: HsDeclP -> Bool Source

Return True if a declaration is a function definition.

isPatBindP :: HsDeclP -> Bool Source

Returns True if a declaration is a pattern binding.

isSimplePatBind :: DataId t => LHsBind t -> Bool Source

Return True if a declaration is a pattern binding which only defines a variable value.

isSimplePatDecl :: DataId t => LHsDecl t -> Bool Source

Return True if a declaration is a pattern binding which only defines a variable value.

isComplexPatBind :: LHsBind name -> Bool Source

Return True if a LHsBin is a pattern binding but not a simple one.

isComplexPatDecl :: LHsDecl name -> Bool Source

Return True if a declaration is a pattern binding but not a simple one.

isFunOrPatBindP :: HsDeclP -> Bool Source

Return True if a declaration is a function/pattern definition.

isFunOrPatBindR :: LHsBind t -> Bool Source

Return True if a declaration is a function/pattern definition.

usedWithoutQualR :: Data t => Name -> t -> Bool Source

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 -> Bool Source

Return True if the identifier is used in the RHS if a function/pattern binding.

findPNT :: Data t => Located Name -> t -> Bool Source

Return True if the identifier occurs in the given syntax phrase.

findPN :: Data t => Name -> t -> Bool Source

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 -> Bool Source

Return True if any of the specified PNames ocuur in the given syntax phrase.

findNamesRdr :: Data t => NameMap -> [Name] -> t -> Bool Source

Return True if any of the specified PNames ocuur in the given syntax phrase.

findEntity :: (FindEntity a, Data b) => a -> b -> Bool Source

Returns True is a syntax phrase, say a, is part of another syntax phrase, say b. NOTE: very important: only do a shallow check

findEntity' :: (Data a, Data b) => a -> b -> Maybe (SimpPos, SimpPos) Source

Returns True is a syntax phrase, say a, is part of another syntax phrase, say b. Expects to be at least Parser output

sameOccurrence :: Located t -> Located t -> Bool Source

Return True if syntax phrases t1 and t2 refer to the same one.

findIdForName :: Name -> RefactGhc (Maybe Id) Source

Return the type checked Id corresponding to the given Name

defines :: Name -> LHsBind Name -> Bool Source

Return True if the function/pattern binding defines the specified identifier.

definesTypeSig :: Name -> LSig Name -> Bool Source

Return True if the declaration defines the type signature of the specified identifier.

Modules and files

Locations

defineLoc :: Located Name -> SrcLoc Source

Return the identifier's defining location. defineLoc::PNT->SrcLoc

useLoc :: Located Name -> SrcLoc Source

Return the identifier's source location. useLoc::PNT->SrcLoc

locToExp Source

Arguments

:: (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.

locToName Source

Arguments

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

locToRdrName Source

Arguments

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

getName Source

Arguments

:: Data t 
=> String

The name to find

-> t

The syntax phrase

-> Maybe Name

The result

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

addDecl Source

Arguments

:: (Data t, Typeable 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.

-> ([LHsDecl RdrName], Maybe Anns)

The declaration with optional signatures to be added, together with optional Annotations.

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

addItemsToImport Source

Arguments

:: ModuleName

The imported module name

-> ParsedSource

The current module

-> [RdrName]

The items to be added ->Maybe GHC.Name -- ^ The condition identifier.

-> RefactGhc ParsedSource

The result

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.

addHiding Source

Arguments

:: ModuleName

The imported module name

-> ParsedSource

The current module

-> [RdrName]

The items to be added

-> RefactGhc ParsedSource

The result

add items to the hiding list of an import declaration which imports the specified module.

addParamsToDecls Source

Arguments

:: [LHsDecl RdrName]

A declaration list where the function is defined and/or used.

-> Name

The function name.

-> [RdrName]

The parameters to be added.

-> RefactGhc [LHsDecl RdrName]

The result.

addImportDecl Source

Arguments

:: ParsedSource 
-> ModuleName 
-> Maybe FastString

qualifier

-> Bool 
-> Bool 
-> Bool 
-> Maybe String

alias

-> Bool 
-> [RdrName] 
-> RefactGhc ParsedSource 

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.

duplicateDecl Source

Arguments

:: [LHsDecl RdrName]

decls to be updated, containing the original decl (and sig)

-> Name

The identifier whose definition is to be duplicated

-> Name

The new name (possibly qualified)

-> RefactGhc [LHsDecl RdrName]

The result

Duplicate a function/pattern binding declaration under a new name right after the original one.

Removing

rmDecl Source

Arguments

:: Data t 
=> Name

The identifier whose definition is to be removed.

-> Bool

True means including the type signature.

-> t

The AST fragment containting the declarations, originating from the ParsedSource

-> RefactGhc (t, LHsDecl RdrName, Maybe (LSig RdrName))

The result and the removed declaration 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.

rmTypeSig Source

Arguments

:: Data t 
=> Name

The identifier whose type signature is to be removed.

-> t

The declarations

-> RefactGhc (t, Maybe (LSig RdrName))

The result and removed signature, if there was one

Remove the type signature that defines the given identifier's type from the declaration list.

rmTypeSigs Source

Arguments

:: Data t 
=> [Name]

The identifiers whose type signatures are to be removed.

-> t

The declarations

-> RefactGhc (t, [LSig RdrName])

The result and removed signatures, if there were any

Remove multiple type signatures

Updating

class (Data t, Data t1) => Update t t1 where Source

Methods

update Source

Arguments

:: t

The syntax phrase to be updated.

-> t

The new syntax phrase.

-> t1

The contex where the old syntax phrase occurs.

-> RefactGhc t1

The result.

Update the occurrence of one syntax phrase in a given scope by another syntax phrase of the same type

Instances

rmQualifier Source

Arguments

:: Data t 
=> [Name]

The identifiers.

-> t

The syntax phrase.

-> RefactGhc t

The result.

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.

renamePN' Source

Arguments

:: Data t 
=> Name

The identifier to be renamed.

-> Name

The new name, including possible qualifier

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

autoRenameLocalVar Source

Arguments

:: Data t 
=> 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.

Miscellous

Parsing, writing and showing

showEntities :: (t -> String) -> [t] -> String Source

Show a list of entities, the parameter f is a function that specifies how to format an entity.

showPNwithLoc :: Located Name -> String Source

Show a PName in a format like: pn(at row:r, col: c).

Locations

Default values

defaultExp :: HsExpP Source

Default expression.

Identifiers, expressions, patterns and declarations

expToName :: LHsExpr Name -> Name Source

If an expression consists of only one identifier then return this identifier in the GHC.Name format, otherwise return the default Name

expToNameRdr :: NameMap -> LHsExpr RdrName -> Maybe Name Source

If an expression consists of only one identifier then return this identifier in the GHC.Name format, otherwise return the default Name

patToNameRdr :: NameMap -> LPat RdrName -> Maybe Name Source

If a pattern consists of only one identifier then return this identifier, otherwise return Nothing

patToPNT :: LPat Name -> Maybe Name Source

If a pattern consists of only one identifier then return this identifier, otherwise return Nothing

pNtoPat :: name -> Pat name Source

Compose a pattern from a pName.

definedPNs :: LHsBind Name -> [Name] Source

Return the list of identifiers (in PName format) defined by a function/pattern binding.

definingDeclsRdrNames Source

Arguments

:: NameMap 
-> [Name]

The specified identifiers.

-> [LHsDecl RdrName]

A collection of declarations.

-> Bool

True means to include the type signature.

-> Bool

True means to look at the local declarations as well.

-> [LHsDecl RdrName]

The result.

Find those declarations(function/pattern binding) which define the specified GHC.Names. incTypeSig indicates whether the corresponding type signature will be included.

definingDeclsRdrNames' Source

Arguments

:: Data t 
=> NameMap 
-> [Name]

The specified identifiers.

-> t

A collection of declarations.

-> [LHsDecl RdrName]

The result.

Find those declarations(function/pattern binding) which define the specified GHC.Names. incTypeSig indicates whether the corresponding type signature will be included.

definingSigsRdrNames Source

Arguments

:: Data t 
=> NameMap 
-> [Name]

The specified identifiers.

-> t

A collection of declarations.

-> [LSig RdrName]

The result.

Find those type signatures for the specified GHC.Names.

definingDeclsNames Source

Arguments

:: [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.

definingDeclsNames' Source

Arguments

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

definingSigsNames Source

Arguments

:: Data t 
=> [Name]

The specified identifiers.

-> t

A collection of declarations.

-> [LSig Name]

The result.

Find those type signatures for the specified GHC.Names.

definingTyClDeclsNames Source

Arguments

:: Data t 
=> [Name]

The specified identifiers.

-> t

A collection of declarations.

-> [LTyClDecl Name]

The result.

Find those declarations which define the specified GHC.Names.

allNames Source

Arguments

:: Data t 
=> t

The syntax phrase

-> [Located Name]

The result

Find all Located Names in the given Syntax phrase.

Others

divideDecls :: Data t => [t] -> Located Name -> RefactGhc ([t], [t], [t]) Source

Divide a declaration list into three parts (before, parent, after) according to the PNT, where parent is the first decl containing the PNT, before are those decls before parent and after are those decls after parent.

mkNewGhcName :: Maybe Module -> String -> RefactGhc Name Source

Make a new GHC.Name, using the Unique Int sequence stored in the RefactState.

mkNewName Source

Arguments

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

causeNameClashInExports Source

Arguments

:: 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

declsSybTransform :: Typeable a => (forall b. HasDecls b => b -> RefactGhc b) -> a -> RefactGhc a Source

Typed AST traversals (added by CMB)

Miscellous

Debug stuff

getParsedForRenamedLPat :: ParsedSource -> LPat Name -> LPat RdrName Source

Given a RenamedSource LPAT, return the equivalent ParsedSource part. NOTE: returns pristine ParsedSource, since HaRe does not change it

getParsedForRenamedName :: ParsedSource -> Located Name -> Located RdrName Source

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

stripLeadingSpaces :: [String] -> [String] Source

Take a list of strings and return a list with the longest prefix of spaces removed

from GhcUtils

SYB versions

everywhereMStaged' :: Monad m => Stage -> GenericM m -> GenericM m Source

Monadic variation on everywhere'

everywhereStaged :: Stage -> (forall a. Data a => a -> a) -> forall a. Data a => a -> a Source

Bottom-up transformation

everywhereStaged' :: Stage -> (forall a. Data a => a -> a) -> forall a. Data a => a -> a Source

Top-down version of everywhereStaged

onelayerStaged :: Stage -> r -> GenericQ r -> GenericQ [r] Source

Perform a query on the immediate subterms only, avoiding holes

listifyStaged :: (Data a, Typeable a1) => Stage -> (a1 -> Bool) -> a -> [a1] Source

Staged variation of SYB.listify The stage must be provided to avoid trying to modify elements which may not be present at all stages of AST processing.

Scrap Your Zipper versions

zeverywhereStaged :: Typeable a => Stage -> GenericT -> Zipper a -> Zipper a Source

Apply a generic transformation everywhere in a bottom-up manner.

zopenStaged :: Typeable a => Stage -> GenericQ Bool -> Zipper a -> [Zipper a] Source

Open a zipper to the point where the Geneneric query passes. returns the original zipper if the query does not pass (check this)

zsomewhereStaged :: MonadPlus m => Stage -> GenericM m -> Zipper a -> m (Zipper a) Source

Apply a generic monadic transformation once at the topmost leftmost successful location, avoiding holes in the GHC structures

transZ :: Stage -> GenericQ Bool -> (Stage -> Zipper a -> Zipper a) -> Zipper a -> Zipper a Source

Transform a zipper opened with a given generic query

transZM :: Monad m => Stage -> GenericQ Bool -> (Stage -> Zipper a -> m (Zipper a)) -> Zipper a -> m (Zipper a) Source

Monadic transform of a zipper opened with a given generic query

zopenStaged' :: Typeable a => Stage -> GenericQ (Maybe b) -> Zipper a -> [(Zipper a, b)] Source

Open a zipper to the point where the Generic query passes, returning the zipper and a value from the specific part of the GenericQ that matched. This allows the components of the query to return a specific transformation routine, to apply to the returned zipper

ztransformStagedM :: (Typeable a, Monad m) => Stage -> GenericQ (Maybe (Stage -> Zipper a -> m (Zipper a))) -> Zipper a -> m (Zipper a) Source

Open a zipper to the point where the Generic query passes, and apply the transformation returned from the specific part of the GenericQ that matched.

SYZ utilities

upUntil :: GenericQ Bool -> Zipper a -> Maybe (Zipper a) Source

Climb the tree until a predicate holds

findAbove :: Data a => (a -> Bool) -> Zipper a -> Maybe a Source

Up the zipper until a predicate holds, and then return the zipper hole

from GhcVersionSpecific

from TokenUtils

from ExactPrint'

replace :: AnnKey -> AnnKey -> Anns -> Maybe Anns Source

Replaces an old expression with a new expression

setRefactAnns :: Anns -> RefactGhc () Source

Internal low level interface to access the current annotations from the RefactGhc state.