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

Portabilityportable
Stabilityexperimental
Maintainercarlo@carlo-hamalainen.net
Safe HaskellNone

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 QualifiedNameSource

Arguments

 = String

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

type SymbolSource

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.

Instances

newtype GhcPkgOptions Source

Constructors

GhcPkgOptions [String]

List of user-supplied ghc-pkg options.

Instances

data HaskellModule Source

Constructors

HaskellModule

Information about an import of a Haskell module.

ghcOptionToGhcPKg :: [String] -> [String]Source

Convert a GHC command line option to a ghc-pkg command line option. This function is incomplete; it only handles a few cases at the moment.

getGhcOptionsViaGhcMod :: IO GhcOptionsSource

Use ghcmod's API to get the GHC options for a project. This uses findCradle, cradlePackageDbOpts, and GhcOptions.

getGHCOptionsViaCradle :: IO [GHCOption]Source

Use ghcmod's API to get the GHC options for a project. This uses findCradle and 'getGHCOptions.'

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

Add user-supplied GHC options to those discovered via ghc-mod.

setDynamicFlags :: GhcMonad m => GhcOptions -> DynFlags -> m ([String], [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 :: GhcOptions -> FilePath -> String -> WriterT [String] IO [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 :: GhcOptions -> FilePath -> String -> IO ([String], [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) -> HaskellModuleSource

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 = []
                }
]

lookupSymbol :: GhcOptions -> FilePath -> String -> String -> [String] -> IO [(Name, [GlobalRdrElt])]Source

Find all matches for a symbol in a source file. The last parameter is a list of imports.

Example:

>>> x <- lookupSymbol "tests/data/data/Hiding.hs" "Hiding" "head" ["Prelude", "Safe", "System.Environment", "Data.List"]
*GhcImportedFrom> putStrLn . (showSDoc tracingDynFlags) . ppr $ x
[(GHC.List.head,
  [GHC.List.head
     imported from `Data.List' at tests/data/data/Hiding.hs:5:1-29
     (and originally defined in `base:GHC.List')])]

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

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 StringSource

Get the module part of a qualified name.

Example:

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

qualifiedName :: GhcOptions -> FilePath -> String -> Int -> Int -> [String] -> IO [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"

ghcPkgFindModule :: GhcPkgOptions -> String -> WriterT [String] IO (Maybe String)Source

Call ghc-pkg find-module to determine that package that provides a module, e.g. Prelude is defined in base-4.6.0.1.

ghcPkgHaddockUrl :: GhcPkgOptions -> String -> WriterT [String] IO (Maybe String)Source

Call ghc-pkg field to get the haddock-html field for a package.

moduleNameToHtmlFile :: String -> StringSource

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

expandMatchingAsImport :: QualifiedName -> [HaskellModule] -> Maybe QualifiedNameSource

If the Haskell module has an import like import qualified Data.List as DL, convert an occurence DL.fromList to the qualified name using the actual module name: Data.List.fromList.

Example:

 -- Muddle.hs

 module Muddle where

 import Data.Maybe
 import qualified Data.List as DL
 import qualified Data.Map as DM
 import qualified Safe

then:

>>> hmodules <- map toHaskellModule <$> getTextualImports "tests/data/data/Muddle.hs" "Muddle"
>>> print $ expandMatchingAsImport "DL.fromList" hmodules
Just "Data.List.fromList"

specificallyMatches :: Symbol -> [HaskellModule] -> [HaskellModule]Source

Return list of modules which explicitly import a symbol.

Example:

 -- Hiding.hs
 module Hiding where
 import Data.List hiding (map)
 import System.Environment (getArgs)
 import qualified Safe
>>> hmodules <- map toHaskellModule <$> getTextualImports "tests/data/data/Hiding.hs" "Hiding"
>>> print $ specificallyMatches "getArgs" hmodules
[ HaskellModule { modName = "System.Environment"
                , modQualifier = Nothing
                , modIsImplicit = False
                , modHiding = []
                , modImportedAs = Nothing
                , modSpecifically = ["getArgs"]
                }
]

toHackageUrl :: FilePath -> String -> String -> StringSource

Convert a file path to a Hackage HTML file to its equivalent on https:hackage.haskell.org.

bestPrefixMatches :: Name -> [GlobalRdrElt] -> [String]Source

When we use parseName to convert a String to a Name we get a list of matches instead of a unique match, so we end up having to guess the best match based on the qualified name.

findHaddockModule :: QualifiedName -> [HaskellModule] -> GhcPkgOptions -> (Name, [GlobalRdrElt]) -> WriterT [String] IO (Maybe String, Maybe String, Maybe String, Maybe String)Source

Find the haddock module. Returns a 4-tuple consisting of: module that the symbol is imported from, haddock url, module, and module's HTML filename.

matchToUrl :: (Maybe String, Maybe String, Maybe String, Maybe String) -> WriterT [String] IO StringSource

Convert our match to a URL, either file: if the file exists, or to hackage.org otherwise.

guessHaddockUrl :: FilePath -> String -> Symbol -> Int -> Int -> GhcOptions -> GhcPkgOptions -> WriterT [String] 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