| Safe Haskell | None | 
|---|
Language.Haskell.HBB.Internal.GHCHighlevel
- searchFunctionBindingM :: GhcMonad m => FilePath -> BufLoc -> Maybe BufLoc -> m FunBindInfo
- searchFunctionBindingForNameM :: GhcMonad m => (Name, BufSpan, FilePath) -> m FunBindInfo
- searchTokenForNameM :: GhcMonad m => (Name, BufSpan, FilePath) -> b -> (b -> b -> b) -> (BufLoc -> GenericQ b) -> m (SearchedTokenInfo b)
- whatIsAt :: GhcMonad m => FilePath -> BufSpan -> m WhatIsAt
- data  WhatIsAt - = ThereIsAnExternalName Name
- | ThereIsAnIEDeclToExtern Name
- | ThereIsAnIEDeclFor WhatIsAt
- | ThereIsANameFor WhatIsAt
- | ThereIsABinding (LHsBindLR Name Name)
- | ThereIsAFunParameter (LPat Name)
- | ThereIsATypeSigFor WhatIsAt
- | UnknownElement
 
- realSrcSpansOfBinding :: Int -> HsBindLR Name Name -> [RealSrcSpan]
- getThingsAt :: (GhcMonad m, Typeable a) => (a -> BufLoc -> Maybe BufSpan) -> FilePath -> BufLoc -> m [a]
- data SearchTokenException
- data LexingFailReason
- data  SearchedTokenInfo a = SearchedTokenInfo {- printFun :: forall b. Outputable b => b -> String
- occSpan :: RealSrcSpan
- name :: Name
- result :: a
 
- type FunBindInfo = SearchedTokenInfo (LHsBindLR Name Name, Maybe (LSig Name))
- data BufSpan = BufSpan BufLoc BufLoc
- data BufLoc = BufLoc Int Int
Documentation
searchFunctionBindingM :: GhcMonad m => FilePath -> BufLoc -> Maybe BufLoc -> m FunBindInfoSource
This function takes a file name and the location that is of interest and searches out the value or function binding for the name that stands at this location. The returned value contains all informations that are needed to inline the function definition or describe how to inline it (smart-inline).
If the name refers to a name that is not part of the module graph (because it has been loaded by a library for example) this function will fail.
searchFunctionBindingForNameM :: GhcMonad m => (Name, BufSpan, FilePath) -> m FunBindInfoSource
This version to search a function binding takes a Name and some details about it.
Arguments
| :: GhcMonad m | |
| => (Name, BufSpan, FilePath) | informations about the Name instance, its location and the file | 
| -> b | neutral result | 
| -> (b -> b -> b) | function to join 2 results | 
| -> (BufLoc -> GenericQ b) | generic query (special cases) for the
   result, produced by  | 
| -> m (SearchedTokenInfo b) | 
This is a generic function that takes informations about a Name and queries the renamed AST according to the parameters.
Arguments
| :: GhcMonad m | |
| => FilePath | The file where the token occurred | 
| -> BufSpan | The location of the token to consider | 
| -> m WhatIsAt | 
This function is responsible to detect what kind of thing is located at the passed location (the token).
Constructors
| ThereIsAnExternalName Name | Names are used for value- and function bindings as well as function parameters. External names refer to things outside of the module graph (external libraries for example) | 
| ThereIsAnIEDeclToExtern Name | (I)mport/(E)xport declaration that points to another compilation unit (package). | 
| ThereIsAnIEDeclFor WhatIsAt | (I)mport/(E)xport declaration that points to the thing stored as first parameter. | 
| ThereIsANameFor WhatIsAt | Names are just pointers to other things. When such a name is discovered, another run of WhatIsAt is triggered which searches for the thing that is at the location pointed to by this name. This can only be a binding (ThereIsABinding) or a function parameter (ThereIsAFunParameter). | 
| ThereIsABinding (LHsBindLR Name Name) | The token pointed to a binding. | 
| ThereIsAFunParameter (LPat Name) | Function parameters are of type (LPat Name) at the location where they are defined. | 
| ThereIsATypeSigFor WhatIsAt | The location specified points to a function or value bindings signature. | 
| UnknownElement | There is something that is currently not supported (e.g. a type declaration). | 
Arguments
| :: Int | Length of the function name (determined by the lexer) | 
| -> HsBindLR Name Name | The actual binding | 
| -> [RealSrcSpan] | A list with one name for each match of the function (or [] if this is a pattern binding or infix declaration) | 
This function extracts the RealSrcSpan elements of a function binding. The problem is that a function binding may contain several entry points of which each has its own src-span attached. Each of these spans will be contained by the result list produced by this function.
This is the heading myfunction in myfunction x = x * x.
Arguments
| :: (GhcMonad m, Typeable a) | |
| => (a -> BufLoc -> Maybe BufSpan) | Tells how to extract the span of an a. If the a element is at the BufLoc specified then the according BufSpan is returned. Note that the results are sorted by the end location of the BufSpan that is returned here. So if this function returns weird data then the sorting of the results is not warranted. | 
| -> FilePath | The filename of the module to be considered. | 
| -> BufLoc | The required start-location of the tokens. | 
| -> m [a] | A sorted list of results. | 
Parses the renamed AST of the module and returns all elements that start at the passed location sorted by length in increasing oder.
data SearchTokenException Source
These are exceptions searchFunctionBinding(M) may throw.
Each exception can be converted to a meaningful string. Moreover searchFunctionBinding is throwing internal errors via error (exception ErrorCall must be catched).
Constructors
| LexingSearchError LexingFailReason | |
| TokenIsntAName | |
| TokenNotEndingAccordingly | |
| IsFunctionApplication | |
| IsExternalName ModuleName | |
| IsntNameOfABinding | 
Instances
| Show SearchTokenException | |
| Typeable SearchTokenException | |
| Exception SearchTokenException | 
data LexingFailReason Source
This type holds possible return values of getVariableIdUsingLexerAt.
Constructors
| LexingFailed | |
| VarNotFound | 
data SearchedTokenInfo a Source
Constructors
| SearchedTokenInfo | |
| Fields 
 | |
type FunBindInfo = SearchedTokenInfo (LHsBindLR Name Name, Maybe (LSig Name))Source
A BufSpan is simply defined by two times a BufLoc.