ghc-imported-from-0.3.0.4: Find the Haddock documentation for a symbol.

CopyrightCarlo Hamalainen 2013-2016
LicenseBSD3
Maintainercarlo@carlo-hamalainen.net
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GhcImportedFrom

Description

Synopsis: Attempt to guess the location of the Haddock HTML documentation for a given symbol in a particular module, file, and line/col location.

Latest development version: https://github.com/carlohamalainen/ghc-imported-from.

Synopsis

Documentation

type QualifiedName Source

Arguments

 = String

A qualified name, e.g. Foo.bar.

type Symbol Source

Arguments

 = String

A symbol, possibly qualified, e.g. bar or Foo.bar.

newtype GhcOptions Source

Constructors

GhcOptions [String]

List of user-supplied GHC options, refer to tets subdirectory for example usage. Note that GHC API and ghc-pkg have inconsistencies in the naming of options, see http://www.vex.net/~trebla/haskell/sicp.xhtml for more details.

newtype GhcPkgOptions Source

Constructors

GhcPkgOptions [String]

List of user-supplied ghc-pkg options.

data HaskellModule Source

Constructors

HaskellModule

Information about an import of a Haskell module.

modifyDFlags :: [String] -> DynFlags -> IO ([GHCOption], DynFlags) Source

Add user-supplied GHC options.

setDynamicFlags :: GhcMonad m => GhcOptions -> DynFlags -> m ([GHCOption], DynFlags) Source

Set GHC options and run initPackages in GhcMonad.

Typical use:

defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
   runGhc (Just libdir) $ do
       getSessionDynFlags >>= setDynamicFlags (GhcOptions myGhcOptionList)
       -- do stuff

getTextualImports :: GhcMonad m => GhcOptions -> FilePath -> String -> m ([GHCOption], [Located (ImportDecl RdrName)]) Source

Read the textual imports in a file.

Example:

>>> (showSDoc tracingDynFlags) . ppr <$> getTextualImports "test/data/Hiding.hs" "Hiding" >>= putStrLn
[ import (implicit) Prelude, import qualified Safe
, import System.Environment ( getArgs )
, import Data.List hiding ( map )
]

See also toHaskellModule and getSummary.

getSummary :: GhcMonad m => GhcOptions -> FilePath -> String -> m ([GHCOption], ModSummary) Source

Get the module summary for a particular file/module. The first and second components of the return value are ghcOpts1 and ghcOpts2; see setDynamicFlags.

toHaskellModule :: Located (ImportDecl RdrName) -> HaskellModule Source

Convenience function for converting an ImportDecl to a HaskellModule.

Example:

-- Hiding.hs
module Hiding where
import Data.List hiding (map)
import System.Environment (getArgs)
import qualified Safe

then:

>>> map toHaskellModule <$> getTextualImports "tests/data/data/Hiding.hs" "Hiding" >>= print
[ HaskellModule { modName = "Prelude"
                , modQualifier = Nothing
                , modIsImplicit = True
                , modHiding = []
                , modImportedAs = Nothing
                , modSpecifically = []
                }
, HaskellModule {modName = "Safe"
                , modQualifier = Nothing
                , modIsImplicit = False
                , modHiding = []
                , modImportedAs = Nothing
                , modSpecifically = []
                }
, HaskellModule { modName = "System.Environment"
                , modQualifier = Nothing
                , modIsImplicit = False
                , modHiding = []
                , modImportedAs = Nothing
                , modSpecifically = ["getArgs"]
                }
, HaskellModule { modName = "Data.List"
                , modQualifier = Nothing
                , modIsImplicit = False
                , modHiding = ["map"]
                , modImportedAs = Nothing
                , modSpecifically = []
                }
]

symbolImportedFrom :: GlobalRdrElt -> [ModuleName] Source

List of possible modules which have resulted in the name being in the current scope. Using a global reader we get the provenance data and then get the list of import specs.

postfixMatch :: Symbol -> QualifiedName -> Bool Source

Returns True if the Symbol matches the end of the QualifiedName.

Example:

>>> postfixMatch "bar" "Foo.bar"
True
>>> postfixMatch "bar" "Foo.baz"
False
>>> postfixMatch "bar" "bar"
True

moduleOfQualifiedName :: QualifiedName -> Maybe String Source

Get the module part of a qualified name.

Example:

>>> moduleOfQualifiedName "Foo.bar"
Just "Foo"
>>> moduleOfQualifiedName "Foo"
Nothing

qualifiedName :: String -> Int -> Int -> [String] -> Ghc [String] Source

Find the possible qualified names for the symbol at line/col in the given Haskell file and module.

Example:

>>> x <- qualifiedName "tests/data/data/Muddle.hs" "Muddle" 27 5 ["Data.Maybe", "Data.List", "Data.Map", "Safe"]
>>> forM_ x print
"AbsBinds [] []\n  {Exports: [Muddle.h <= h\n               <>]\n   Exported types: Muddle.h\n                     :: Data.Map.Base.Map GHC.Base.String GHC.Base.String\n                   [LclId]\n   Binds: h = Data.Map.Base.fromList [(\"x\", \"y\")]}"
"h = Data.Map.Base.fromList [(\"x\", \"y\")]"
"Data.Map.Base.fromList [(\"x\", \"y\")]"
"Data.Map.Base.fromList"

moduleNameToHtmlFile :: String -> String Source

Convert a module name string, e.g. Data.List to Data-List.html.

matchToUrl :: (Maybe String, Maybe String, Maybe String, Maybe String) -> IO String Source

Convert our match to a URL of the form file:// so that we can open it in a web browser.

guessHaddockUrl :: FilePath -> String -> Symbol -> Int -> Int -> GhcOptions -> GhcPkgOptions -> IO (Either String String) Source

Attempt to guess the Haddock url, either a local file path or url to hackage.haskell.org for the symbol in the given file, module, at the specified line and column location.

Example:

>>> guessHaddockUrl "tests/data/data/Muddle.hs" "Muddle" "Maybe" 11 11
(lots of output)
SUCCESS: file:///home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/Data-Maybe.html

haddockUrl :: Options -> FilePath -> String -> String -> Int -> Int -> IO String Source

Top level function; use this one from src/Main.hs.

getGhcOptionsViaCabalRepl :: IO (Maybe [String]) Source

Use "cabal repl" with our fake ghc binary to get all the GHC options related to the local cabal sandbox (if present).