HaRe-0.8.2.1: the Haskell Refactorer.

Safe HaskellNone
LanguageHaskell98

Language.Haskell.Refact.Utils.Variables

Contents

Description

 

Synopsis

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

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

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]

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

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

Methods

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.

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.

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

allNames Source

Arguments

:: Data t 
=> t

The syntax phrase

-> [Located Name]

The result

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.

hsNamess :: Data t => t -> [Name] Source

Get all the names in the given syntax element

hsNamessRdr :: Data t => t -> [Located RdrName] Source

Get all the names in the given syntax element

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.