HaRe-0.8.4.1: the Haskell Refactorer.

Safe HaskellNone
LanguageHaskell98

Language.Haskell.Refact.Utils.TypeUtils

Contents

Description

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.

Synopsis

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

:: NameMap 
-> Name

The identifier

-> ParsedSource

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.

hsQualifier Source #

Arguments

:: Name

The identifier.

-> RefactGhc [ModuleName]

The result.

Return all the possible qualifiers for the identifier. The identifier is not inscope if the result is an empty list. NOTE: This is intended to be used when processing a client module, so the Name parameter is actually from a different module.

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

isTypeSigDecl :: LHsDecl a -> Bool Source #

Return True if a declaration is a type signature declaration.

isFunBindP :: LHsDecl RdrName -> Bool Source #

Return True if a declaration is a function definition.

isPatBindP :: LHsDecl RdrName -> 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 :: LHsDecl RdrName -> 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.

Getting

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

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

Return the type checked Id corresponding to the given Name

definesTypeSigRdr :: NameMap -> Name -> Sig RdrName -> Bool Source #

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

class Data t => UsedByRhs t where Source #

Minimal complete definition

usedByRhsRdr

Methods

usedByRhsRdr :: NameMap -> t -> [Name] -> Bool Source #

Return True if any of the GHC.Name's appear in the given syntax element

Instances

UsedByRhs DocDecl Source # 
UsedByRhs [LHsDecl RdrName] Source # 
UsedByRhs [LIE RdrName] Source # 

Methods

usedByRhsRdr :: NameMap -> [LIE RdrName] -> [Name] -> Bool Source #

UsedByRhs a => UsedByRhs (Maybe a) Source # 

Methods

usedByRhsRdr :: NameMap -> Maybe a -> [Name] -> Bool Source #

UsedByRhs (HsModule RdrName) Source # 
UsedByRhs (HsDecl RdrName) Source # 
UsedByRhs (SpliceDecl RdrName) Source # 
UsedByRhs (TyClDecl RdrName) Source # 
UsedByRhs (InstDecl RdrName) Source # 
UsedByRhs (DerivDecl RdrName) Source # 
UsedByRhs (DefaultDecl RdrName) Source # 
UsedByRhs (ForeignDecl RdrName) Source # 
UsedByRhs (RuleDecls RdrName) Source # 
UsedByRhs (VectDecl RdrName) Source # 
UsedByRhs (WarnDecls RdrName) Source # 
UsedByRhs (AnnDecl RdrName) Source # 
UsedByRhs (RoleAnnotDecl RdrName) Source # 
UsedByRhs (HsBind RdrName) Source # 
UsedByRhs (Sig RdrName) Source # 
UsedByRhs (HsExpr RdrName) Source # 
UsedByRhs (IE RdrName) Source # 
UsedByRhs a => UsedByRhs (Located a) Source # 

Methods

usedByRhsRdr :: NameMap -> Located a -> [Name] -> Bool Source #

UsedByRhs (Match RdrName (LHsExpr RdrName)) Source # 
UsedByRhs (Stmt RdrName (LHsExpr RdrName)) Source # 

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

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

-> Maybe Name

The condition identifier.

-> Either [RdrName] [LIE RdrName]

The items to be added

-> ParsedSource

The current module

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

addItemsToExport Source #

Arguments

:: ParsedSource

The module AST.

-> Maybe Name

The condtion identifier.

-> Bool

Create an explicit list or not

-> Either [RdrName] [LIE RdrName]

The identifiers to add in either String or HsExportEntP format.

-> RefactGhc ParsedSource

The result.

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 empty, then if the third argument is True, then create an explict export list to contain only the new identifiers, otherwise do nothing. TODO:AZ: re-arrange params to line up with addItemsToExport

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 StringLiteral

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

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

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

Identifiers, expressions, patterns and declarations

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

pNtoPat :: name -> Pat name Source #

Deprecated: Can't use Renamed in GHC 8

Compose a pattern from a pName.

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

Return True if the identifier is unqualifiedly used in the given syntax phrase. Check in a way that the test can be done in a client module, i.e. not using the nameUnique usedWithoutQualR :: GHC.Name -> GHC.ParsedSource -> Bool

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.

mkRdrName :: String -> RdrName Source #

Make a simple unqualified RdrName

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.

registerRdrName :: Located RdrName -> RefactGhc () Source #

Register a Located RdrName in the NameMap so it can be looked up if needed. This will create a brand new Name, so no guarantees are given as to matches later. Perhaps this is a bad idea.

causeNameClashInExports Source #

Arguments

:: NameMap 
-> Name

The original name

-> Name

The new name

-> ModuleName

The identity of the module

-> ParsedSource

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