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

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

Minimal complete definition

findEntity

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

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 #

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.

definingTyClDeclsNames Source #

Arguments

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

findLRdrName :: Data t => NameMap -> Name -> t -> Bool Source #

Does the given Name appear as a Located RdrName anywhere in t?

locToNameRdr Source #

Arguments

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

locToNameRdrPure Source #

Arguments

:: Data t 
=> NameMap 
-> SimpPos

The row and column number

-> t

The syntax phrase, parameterised by RdrName

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

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.