Safe Haskell | None |
---|---|
Language | Haskell98 |
- isFieldName :: Name -> Bool
- isClassName :: Name -> Bool
- isInstanceName :: Name -> Bool
- isDeclaredIn :: HsValBinds t Name => Name -> t -> Bool
- isDeclaredInRdr :: NameMap -> Name -> [LHsDecl RdrName] -> Bool
- data FreeNames = FN {}
- data DeclaredNames = DN {}
- hsFreeAndDeclaredPNsOld :: Data t => t -> ([Name], [Name])
- hsFreeAndDeclaredRdr :: Data t => NameMap -> t -> (FreeNames, DeclaredNames)
- hsFreeAndDeclaredNameStrings :: (Data t, Outputable t) => t -> RefactGhc ([String], [String])
- hsFreeAndDeclaredPNs :: Data t => t -> RefactGhc ([Name], [Name])
- hsFreeAndDeclaredGhc :: Data t => t -> RefactGhc (FreeNames, DeclaredNames)
- getDeclaredTypes :: LTyClDecl Name -> [Name]
- getDeclaredTypesRdr :: LHsDecl RdrName -> RefactGhc [Name]
- getFvs :: [LHsBind Name] -> [([Name], NameSet)]
- getFreeVars :: [LHsBind Name] -> [Name]
- getDeclaredVars :: [LHsBind Name] -> [Name]
- hsVisiblePNs :: (FindEntity e, HsValBinds t Name, Outputable e) => e -> t -> RefactGhc [Name]
- hsVisiblePNsRdr :: (FindEntity e, Data t, Outputable e) => NameMap -> e -> t -> RefactGhc [Name]
- hsVisibleNames :: (FindEntity t1, HsValBinds t2 Name, Outputable t1) => t1 -> t2 -> RefactGhc [String]
- hsVisibleNamesRdr :: (FindEntity t1, Data t2, Outputable t1) => t1 -> t2 -> RefactGhc [String]
- hsFDsFromInsideRdr :: Data t => NameMap -> t -> RefactGhc (FreeNames, DeclaredNames)
- hsFDNamesFromInsideRdr :: Data t => t -> RefactGhc ([String], [String])
- hsFDsFromInside :: Data t => t -> RefactGhc ([Name], [Name])
- hsFDNamesFromInside :: Data t => t -> RefactGhc ([String], [String])
- hsVisibleDs :: (FindEntity e, Outputable e, Data t, HsValBinds t Name) => e -> t -> RefactGhc DeclaredNames
- hsVisibleDsRdr :: (FindEntity e, Outputable e, Data t) => NameMap -> e -> t -> RefactGhc DeclaredNames
- rdrName2Name :: Located RdrName -> RefactGhc Name
- rdrName2NamePure :: NameMap -> Located RdrName -> Name
- eqRdrNamePure :: NameMap -> Located RdrName -> Name -> Bool
- rdrName2Name' :: Located RdrName -> RefactGhc Name
- class (Data a, Typeable a) => FindEntity a where
- findEntity :: Data b => a -> b -> Bool
- sameOccurrence :: Located t -> Located t -> Bool
- definedPNs :: LHsBind Name -> [Name]
- 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]
- definingDeclsNames :: [Name] -> [LHsBind Name] -> Bool -> Bool -> [LHsBind Name]
- definingDeclsNames' :: Data t => [Name] -> t -> [LHsBind Name]
- definingSigsNames :: Data t => [Name] -> t -> [LSig Name]
- definingTyClDeclsNames :: Data t => [Name] -> t -> [LTyClDecl Name]
- defines :: Name -> LHsBind Name -> Bool
- definesRdr :: NameMap -> Name -> LHsBind RdrName -> Bool
- definesDeclRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool
- definesTypeSig :: Name -> LSig Name -> Bool
- definesTypeSigRdr :: NameMap -> Name -> Sig RdrName -> Bool
- definesSigDRdr :: NameMap -> Name -> LHsDecl RdrName -> Bool
- definesP :: PName -> HsDeclP -> Bool
- allNames :: Data t => t -> [Located Name]
- hsPNs :: Data t => t -> [PName]
- hsNamess :: Data t => t -> [Name]
- hsNamessRdr :: Data t => t -> [Located RdrName]
- locToName :: Data t => SimpPos -> t -> Maybe (Located 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
isDeclaredIn :: HsValBinds t Name => Name -> t -> Bool Source
For free variables
data DeclaredNames Source
For declared variables
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
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, Outputable t) => t -> RefactGhc ([String], [String]) Source
The same as hsFreeAndDeclaredPNs
except that the returned
variables are in the String format.
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
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]
getFreeVars :: [LHsBind Name] -> [Name] Source
getDeclaredVars :: [LHsBind Name] -> [Name] Source
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 [].
hsVisibleDsRdr :: (FindEntity e, Outputable e, Data t) => NameMap -> 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 [].
Identifiers, expressions, patterns and declarations
class (Data a, Typeable a) => FindEntity a where Source
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
sameOccurrence :: Located t -> Located t -> Bool Source
Return True if syntax phrases t1 and t2 refer to the same one.
definedPNs :: LHsBind Name -> [Name] Source
Return the list of identifiers (in PName format) defined by a function/pattern binding.
:: 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.
:: 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.
:: [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.
:: Data t | |
=> [Name] | The specified identifiers. |
-> t | A collection of declarations. |
-> [LTyClDecl Name] | The result. |
Find those declarations which define the specified GHC.Names.
defines :: Name -> LHsBind Name -> Bool Source
Return True if the function/pattern binding defines the specified identifier.
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
definesTypeSig :: Name -> LSig Name -> Bool Source
Return True if the declaration defines the type signature of the specified identifier.
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
Find all Located Names in the given Syntax phrase.
hsPNs :: Data t => t -> [PName] Source
Collect the identifiers (in PName format) in a given syntax phrase.
hsNamessRdr :: Data t => t -> [Located RdrName] Source
Get all the names in the given syntax element
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.