Safe Haskell | None |
---|
- type GHCApplyFunction a = FilePath -> TypecheckedModule -> Ghc a
- getAST :: FilePath -> FilePath -> String -> [String] -> IO (OpResult (Maybe TypecheckedSource))
- withAST :: (TypecheckedModule -> Ghc a) -> FilePath -> FilePath -> String -> [String] -> IO (Maybe a)
- withJSONAST :: (Value -> IO a) -> FilePath -> FilePath -> String -> [String] -> IO (Maybe a)
- withASTNotes :: GHCApplyFunction a -> (FilePath -> FilePath) -> FilePath -> LoadContents -> [String] -> IO (OpResult [a])
- ghcMessagesToNotes :: DynFlags -> FilePath -> Messages -> [BWNote]
- getGhcNamesInScope :: FilePath -> FilePath -> String -> [String] -> IO [String]
- getGhcNameDefsInScope :: FilePath -> FilePath -> String -> [String] -> IO (OpResult (Maybe [NameDef]))
- getThingAtPointJSON :: Int -> Int -> FilePath -> FilePath -> String -> [String] -> IO (Maybe ThingAtPoint)
- getLocalsJSON :: Int -> Int -> Int -> Int -> FilePath -> FilePath -> String -> [String] -> IO [ThingAtPoint]
- ghcSpanToLocation :: SrcSpan -> InFileSpan
- ghcSpanToBWLocation :: FilePath -> SrcSpan -> BWLocation
- ghcColToScionCol :: Int -> Int
- scionColToGhcCol :: Int -> Int
- ghctokensArbitrary :: FilePath -> String -> [String] -> IO (Either BWNote [Located Token])
- lexLoc :: RealSrcLoc
- lexerFlags :: [ExtensionFlag]
- ofInterest :: Located Token -> Bool
- tokenToType :: Located Token -> TokenDef
- tokenTypesArbitrary :: FilePath -> String -> Bool -> [String] -> IO (Either BWNote [TokenDef])
- occurrences :: FilePath -> String -> Text -> Bool -> [String] -> IO (Either BWNote [TokenDef])
- generateTokens :: FilePath -> String -> Bool -> [String] -> ([Located Token] -> [TokenDef]) -> ([TokenDef] -> a) -> IO (Either BWNote a)
- preprocessSource :: String -> Bool -> ([TokenDef], String)
- data PPBehavior
- ghcErrMsgToNote :: DynFlags -> FilePath -> ErrMsg -> BWNote
- ghcWarnMsgToNote :: DynFlags -> FilePath -> WarnMsg -> BWNote
- ghcMsgToNote :: DynFlags -> BWNoteStatus -> FilePath -> ErrMsg -> BWNote
- removeStatus :: BWNoteStatus -> String -> String
- mkUnqualTokenValue :: FastString -> Text
- mkQualifiedTokenValue :: FastString -> FastString -> Text
- mkTokenName :: Token -> Text
- tokenType :: Token -> Text
- dotFS :: FastString
- tokenValue :: Bool -> Token -> Text
- start :: SrcSpan -> (Int, Int)
- end :: SrcSpan -> (Int, Int)
- type AliasMap = Map ModuleName [ModuleName]
- ghcImportToUsage :: Text -> LImportDecl Name -> ([Usage], AliasMap) -> Ghc ([Usage], AliasMap)
- ghcLIEToUsage :: DynFlags -> Maybe Text -> Text -> Text -> LIE Name -> [Usage]
- ghcExportToUsage :: DynFlags -> Text -> Text -> AliasMap -> LIE Name -> Ghc [Usage]
- ghcNameToUsage :: DynFlags -> Maybe Text -> Text -> Text -> Name -> SrcSpan -> Bool -> Usage
Documentation
type GHCApplyFunction a = FilePath -> TypecheckedModule -> Ghc aSource
:: FilePath | the source file |
-> FilePath | the base directory |
-> String | the module name |
-> [String] | the GHC options |
-> IO (OpResult (Maybe TypecheckedSource)) |
get the GHC typechecked AST
:: (TypecheckedModule -> Ghc a) | the action |
-> FilePath | the source file |
-> FilePath | the base directory |
-> String | the module name |
-> [String] | the GHC options |
-> IO (Maybe a) |
perform an action on the GHC Typechecked module
:: (Value -> IO a) | the action |
-> FilePath | the source file |
-> FilePath | the base directory |
-> String | the module name |
-> [String] | the GHC options |
-> IO (Maybe a) |
perform an action on the GHC JSON AST
:: GHCApplyFunction a | the final action to perform on the result |
-> (FilePath -> FilePath) | transform given file path to find bwinfo path |
-> FilePath | the base directory |
-> LoadContents | what to load |
-> [String] | the GHC options |
-> IO (OpResult [a]) |
the main method loading the source contents into GHC
Convert Messages
to '[BWNote]'.
This will mix warnings and errors, but you can split them back up
by filtering the '[BWNote]' based on the bw_status
.
:: FilePath | source path |
-> FilePath | base directory |
-> String | module name |
-> [String] | build options |
-> IO [String] |
get all names in scope
:: FilePath | source path |
-> FilePath | base directory |
-> String | module name |
-> [String] | build options |
-> IO (OpResult (Maybe [NameDef])) |
get all names in scope, packaged in NameDefs
:: Int | line |
-> Int | column -> Bool ^ do we want the result qualified by the module -> Bool ^ do we want the full type or just the haddock type |
-> FilePath | source file path |
-> FilePath | base directory |
-> String | module name |
-> [String] | build flags |
-> IO (Maybe ThingAtPoint) |
get the thing at a particular point (line/column) in the source this is using the saved JSON info if available
:: Int | start line |
-> Int | start column |
-> Int | end line |
-> Int | end column |
-> FilePath | source file path |
-> FilePath | base directory |
-> String | module name |
-> [String] | build flags |
-> IO [ThingAtPoint] |
get the thing at a particular point (line/column) in the source this is using the saved JSON info if available
ghcSpanToLocation :: SrcSpan -> InFileSpanSource
convert a GHC SrcSpan to a Span, ignoring the actual file info
:: FilePath | Base directory |
-> SrcSpan | |
-> BWLocation |
convert a GHC SrcSpan to a BWLocation
ghcColToScionCol :: Int -> IntSource
convert a column info from GHC to our system (1 based)
scionColToGhcCol :: Int -> IntSource
convert a column info from our system (1 based) to GHC
:: FilePath | The file path to the document |
-> String | The document's contents |
-> [String] | The options |
-> IO (Either BWNote [Located Token]) |
Get a stream of tokens generated by the GHC lexer from the current document
ofInterest :: Located Token -> BoolSource
Filter tokens whose span appears legitimate (start line is less than end line, start column is less than end column.)
tokenToType :: Located Token -> TokenDefSource
Convert a GHC token to an interactive token (abbreviated token type)
tokenTypesArbitrary :: FilePath -> String -> Bool -> [String] -> IO (Either BWNote [TokenDef])Source
Generate the interactive token list used by EclipseFP for syntax highlighting
:: FilePath | Project root or base directory for absolute path conversion |
-> String | Contents to be parsed |
-> Text | Token value to find |
-> Bool | Literate source flag (True = literate, False = ordinary) |
-> [String] | Options |
-> IO (Either BWNote [TokenDef]) |
Extract occurrences based on lexing
:: FilePath | The project's root directory |
-> String | The current document contents, to be parsed |
-> Bool | Literate Haskell flag |
-> [String] | The options |
-> ([Located Token] -> [TokenDef]) | Transform function from GHC tokens to TokenDefs |
-> ([TokenDef] -> a) | The TokenDef filter function |
-> IO (Either BWNote a) |
Parse the current document, generating a TokenDef list, filtered by a function
:: String | the source contents |
-> Bool | is the source literate Haskell |
-> ([TokenDef], String) | the preprocessor tokens and the final valid Haskell source |
Preprocess some source, returning the literate and Haskell source as tuple.
ghcErrMsgToNote :: DynFlags -> FilePath -> ErrMsg -> BWNoteSource
convert a GHC error message to our note type
ghcWarnMsgToNote :: DynFlags -> FilePath -> WarnMsg -> BWNoteSource
convert a GHC warning message to our note type
ghcMsgToNote :: DynFlags -> BWNoteStatus -> FilePath -> ErrMsg -> BWNoteSource
removeStatus :: BWNoteStatus -> String -> StringSource
remove the initial status text from a message
:: FastString | the qualifier |
-> FastString | the name |
-> Text |
make qualified token: join the qualifier and the name by a dot
mkTokenName :: Token -> TextSource
Make a token definition from its source location and Lexer.hs token type. mkTokenDef :: Located Token -> TokenDef mkTokenDef (L sp t) = TokenDef (mkTokenName t) (ghcSpanToLocation sp)
tokenValue :: Bool -> Token -> TextSource
type AliasMap = Map ModuleName [ModuleName]Source
ghcImportToUsage :: Text -> LImportDecl Name -> ([Usage], AliasMap) -> Ghc ([Usage], AliasMap)Source