Safe Haskell | None |
---|---|
Language | Haskell98 |
- isFieldName :: Name -> Bool
- isClassName :: Name -> Bool
- isInstanceName :: Name -> Bool
- isDeclaredInRdr :: NameMap -> Name -> [LHsDecl RdrName] -> Bool
- data FreeNames = FN {}
- data DeclaredNames = DN {}
- hsFreeAndDeclaredRdr :: Data t => NameMap -> t -> (FreeNames, DeclaredNames)
- hsFreeAndDeclaredNameStrings :: Data t => t -> RefactGhc ([String], [String])
- hsFreeAndDeclaredPNs :: Data t => t -> RefactGhc ([Name], [Name])
- getDeclaredTypesRdr :: LHsDecl RdrName -> RefactGhc [Name]
- getDeclaredVarsRdr :: NameMap -> [LHsDecl RdrName] -> [Name]
- hsVisibleNamesRdr :: Data t2 => Name -> t2 -> RefactGhc [String]
- hsFDsFromInsideRdr :: Data t => NameMap -> t -> (FreeNames, DeclaredNames)
- hsFDNamesFromInsideRdr :: Data t => t -> RefactGhc ([String], [String])
- hsFDNamesFromInsideRdrPure :: Data t => NameMap -> t -> ([String], [String])
- hsVisibleDsRdr :: Data t => NameMap -> Name -> t -> RefactGhc DeclaredNames
- rdrName2Name :: Located RdrName -> RefactGhc Name
- rdrName2NamePure :: NameMap -> Located RdrName -> Name
- eqRdrNamePure :: NameMap -> Located RdrName -> Name -> Bool
- class (Data a, Typeable a) => FindEntity a where
- findNameInRdr :: Data t => NameMap -> Name -> t -> Bool
- findNamesRdr :: Data t => NameMap -> [Name] -> t -> Bool
- sameOccurrence :: Located t -> Located t -> Bool
- definedPNsRdr :: LHsDecl RdrName -> [Located RdrName]
- definedNamesRdr :: NameMap -> LHsDecl RdrName -> [Name]
- definingDeclsRdrNames :: NameMap -> [Name] -> [LHsDecl RdrName] -> Bool -> Bool -> [LHsDecl RdrName]
- definingDeclsRdrNames' :: Data t => NameMap -> [Name] -> t -> [LHsDecl RdrName]
- definingSigsRdrNames :: Data t => NameMap -> [Name] -> t -> [LSig RdrName]
- definingTyClDeclsNames :: Data t => NameMap -> [Name] -> t -> [LTyClDecl RdrName]
- definesRdr :: NameMap -> Name -> LHsBind RdrName -> Bool
- definesDeclRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool
- definesTypeSigRdr :: NameMap -> Name -> Sig RdrName -> Bool
- definesSigDRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool
- hsTypeVbls :: Data t => t -> ([RdrName], [RdrName])
- hsNamessRdr :: Data t => t -> [Located RdrName]
- findLRdrName :: Data t => NameMap -> Name -> t -> Bool
- locToNameRdr :: Data t => SimpPos -> t -> RefactGhc (Maybe Name)
- locToNameRdrPure :: Data t => NameMap -> SimpPos -> t -> Maybe Name
- locToRdrName :: Data t => SimpPos -> t -> Maybe (Located RdrName)
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
For free variables
data DeclaredNames Source #
For declared variables
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
hsFreeAndDeclaredNameStrings :: Data t => t -> RefactGhc ([String], [String]) Source #
The same as hsFreeAndDeclaredPNs
except that the returned
variables are in the String format.
hsFreeAndDeclaredPNs :: Data t => t -> RefactGhc ([Name], [Name]) Source #
Return the free and declared Names in the given syntax fragment. The syntax fragment MUST be parameterised by RdrName, else the empty list will be returned.
getDeclaredTypesRdr :: LHsDecl RdrName -> RefactGhc [Name] Source #
Get the names of all types declared in the given declaration getDeclaredTypesRdr :: GHC.LTyClDecl GHC.RdrName -> RefactGhc [GHC.Name]
hsVisibleNamesRdr :: Data t2 => Name -> t2 -> RefactGhc [String] Source #
Same as hsVisiblePNsRdr
except that the returned identifiers are
in String format.
hsFDsFromInsideRdr :: Data t => NameMap -> t -> (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 ParsedSource
hsFDNamesFromInsideRdr :: Data t => t -> RefactGhc ([String], [String]) Source #
The same as hsFDsFromInside
except that the returned variables
are in the String format
hsFDNamesFromInsideRdrPure :: Data t => NameMap -> t -> ([String], [String]) Source #
The same as hsFDsFromInside
except that the returned variables
are in the String format
hsVisibleDsRdr :: Data t => NameMap -> Name -> t -> RefactGhc DeclaredNames Source #
Given a Name
n and a syntax phrase t, if n occurs in t, then return those
variables which are declared in t and accessible to n, otherwise
return [].
Identifiers, expressions, patterns and declarations
class (Data a, Typeable a) => FindEntity a where Source #
Deprecated: Can't use Renamed in GHC 8
findEntity :: 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
findNameInRdr :: Data t => NameMap -> Name -> t -> Bool Source #
Return True if the specified Name ocuurs 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.
sameOccurrence :: Located t -> Located t -> Bool Source #
Return True if syntax phrases t1 and t2 refer to the same one.
definingDeclsRdrNames Source #
:: 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 #
:: 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.
:: 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.
definingTyClDeclsNames Source #
:: Data t | |
=> NameMap | |
-> [Name] | The specified identifiers. |
-> t | A collection of declarations. |
-> [LTyClDecl RdrName] | The result. |
Find those declarations which define the specified GHC.Names.
definesRdr :: NameMap -> Name -> LHsBind RdrName -> Bool Source #
Return True if the function/pattern binding defines the specified identifier.
definesDeclRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool Source #
Unwraps a LHsDecl and calls definesRdr on the result if a HsBind
definesTypeSigRdr :: NameMap -> Name -> Sig RdrName -> Bool Source #
Return True if the declaration defines the type signature of the specified identifier.
definesSigDRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool Source #
Unwraps a LHsDecl and calls definesRdr on the result if a Sig
hsTypeVbls :: Data t => t -> ([RdrName], [RdrName]) Source #
Collect those type variables that are declared in a given syntax phrase t. In the returned result, the first list is always be empty.
hsNamessRdr :: Data t => t -> [Located RdrName] Source #
Get all the names in the given syntax element
:: Data t | |
=> SimpPos | The row and column number |
-> t | The syntax phrase, parameterised by RdrName |
-> RefactGhc (Maybe 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.