module Language.Haskell.GhcImportedFrom (
QualifiedName
, Symbol
, GhcOptions(..)
, GhcPkgOptions(..)
, HaskellModule(..)
, modifyDFlags
, setDynamicFlags
, getTextualImports
, getSummary
, toHaskellModule
, lookupSymbol
, symbolImportedFrom
, postfixMatch
, moduleOfQualifiedName
, qualifiedName
, ghcPkgFindModule
, ghcPkgHaddockUrl
, moduleNameToHtmlFile
, expandMatchingAsImport
, specificallyMatches
, toHackageUrl
, bestPrefixMatches
, findHaddockModule
, matchToUrl
, guessHaddockUrl
, haddockUrl
, getGhcOptionsViaCabalRepl
, Options (..)
, defaultOptions
, LineSeparator (..)
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Instances()
import Control.Monad.Writer
import Data.Function (on)
import Data.List
import Data.Maybe
import Data.Typeable()
import Desugar()
import DynFlags
import FastString
import GHC
import GHC.Paths (libdir)
import GHC.SYB.Utils()
import HscTypes
import Name
import Outputable
import RdrName
import System.Directory
import System.Environment()
import System.FilePath
import System.IO
import System.Process
import TcRnTypes()
import qualified DynFlags()
import qualified GhcMonad
import qualified MonadUtils()
import qualified Packages
import qualified SrcLoc
import qualified Safe
import Language.Haskell.GhcMod (
findCradle
, cradleRootDir
, Cradle(..)
)
import Language.Haskell.GhcImportedFrom.UtilsFromGhcMod
import Language.Haskell.GhcImportedFrom.Types
import Control.Exception (SomeException)
#if __GLASGOW_HASKELL__ >= 708
import DynFlags ( unsafeGlobalDynFlags )
tdflags = unsafeGlobalDynFlags
#else
import DynFlags ( tracingDynFlags )
tdflags = tracingDynFlags
#endif
type GHCOption = String
getGhcOptionsViaCabalRepl :: IO (Maybe [String])
getGhcOptionsViaCabalRepl = do
(Just _, Just hout, Just _, _) <- createProcess (proc "cabal" ["repl", "--with-ghc=fake-ghc-for-ghc-imported-from"]){ std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe }
ineof <- hIsEOF hout
result <- if ineof
then return ""
else do firstLine <- hGetLine hout
if "GHCi" `isPrefixOf` firstLine
then return "DERP"
else do rest <- readRestOfHandle hout
return $ firstLine ++ "\n" ++ rest
let result' = filter ("--interactive" `isPrefixOf`) . lines $ result
case length result' of 1 -> return $ Just $ filterOpts $ words $ head result'
_ -> return Nothing
where filterOpts :: [String] -> [String]
filterOpts xs = filter (\x -> x /= "--interactive" && x /= "-fbuilding-cabal-package") $ dropModuleNames xs
dropModuleNames :: [String] -> [String]
dropModuleNames xs = reverse $ dropWhile (not . ("-" `isPrefixOf`)) (reverse xs)
getGhcOptionsViaCabalReplOrEmpty :: IO [String]
getGhcOptionsViaCabalReplOrEmpty = liftM (fromMaybe []) getGhcOptionsViaCabalRepl
type QualifiedName = String
type Symbol = String
newtype GhcOptions
= GhcOptions [String] deriving (Show)
newtype GhcPkgOptions
= GhcPkgOptions [String] deriving (Show)
data HaskellModule
= HaskellModule { modName :: String
, modQualifier :: Maybe String
, modIsImplicit :: Bool
, modHiding :: [String]
, modImportedAs :: Maybe String
, modSpecifically :: [String]
} deriving (Show, Eq)
modifyDFlags :: [String] -> DynFlags -> IO ([String], [GHCOption], DynFlags)
modifyDFlags ghcOpts0 dflags0 =
runGhc (Just libdir) $ do
ghcOpts1 <- GhcMonad.liftIO getGhcOptionsViaCabalReplOrEmpty
(dflags1, _, _) <- GHC.parseDynamicFlags dflags0 (map SrcLoc.noLoc $ ghcOpts0 ++ ghcOpts1)
let dflags2 = dflags1 { hscTarget = HscInterpreted
, ghcLink = LinkInMemory
}
return ([], [], dflags2)
setDynamicFlags :: GhcMonad m => GhcOptions -> DynFlags -> m ([String], [GHCOption], DynFlags)
setDynamicFlags (GhcOptions extraGHCOpts) dflags0 = do
(ghcOpts1, ghcOpts2, dflags1) <- GhcMonad.liftIO $ modifyDFlags extraGHCOpts dflags0
void $ setSessionDynFlags dflags1
_ <- GhcMonad.liftIO $ Packages.initPackages dflags1
return (ghcOpts1, ghcOpts2, dflags1)
getTextualImports :: GhcOptions -> FilePath -> String -> IO [SrcLoc.Located (ImportDecl RdrName)]
getTextualImports ghcopts targetFile targetModuleName = do
putStrLn $ "getTextualImports: " ++ show (targetFile, targetModuleName)
(ghcOpts1, ghcOpts2, modSum) <- getSummary ghcopts targetFile targetModuleName
putStrLn $ "getTextualImports: ghcOpts1: " ++ show ghcOpts1
putStrLn $ "getTextualImports: ghcOpts2: " ++ show ghcOpts2
return $ ms_textual_imps modSum
getSummary :: GhcOptions -> FilePath -> String -> IO ([String], [GHCOption], ModSummary)
getSummary ghcopts targetFile targetModuleName =
runGhc (Just libdir) $ do
GhcMonad.liftIO $ putStrLn $ "getSummary, setting dynamic flags..."
(ghcOpts1, ghcOpts2, _) <- getSessionDynFlags >>= setDynamicFlags ghcopts
GhcMonad.liftIO $ putStrLn $ "getSummary, loading the target file..."
target <- guessTarget targetFile Nothing
setTargets [target]
_ <- load LoadAllTargets
GhcMonad.liftIO $ putStrLn $ "getSummary, setting the context..."
(setContext [(IIDecl . simpleImportDecl . mkModuleName) targetModuleName])
`gcatch` (\(_ :: SourceError) -> GhcMonad.liftIO (putStrLn "getSummary: setContext failed with a SourceError, trying to continue anyway..."))
`gcatch` (\(_ :: GhcApiError) -> GhcMonad.liftIO (putStrLn "getSummary: setContext failed with a GhcApiError, trying to continue anyway..."))
`gcatch` (\(_ :: SomeException) -> GhcMonad.liftIO (putStrLn "getSummary: setContext failed with a SomeException, trying to continue anyway..."))
GhcMonad.liftIO $ putStrLn $ "getSummary, extracting the module summary..."
modSum <- getModSummary (mkModuleName targetModuleName)
return (ghcOpts1, ghcOpts2, modSum)
toHaskellModule :: SrcLoc.Located (GHC.ImportDecl GHC.RdrName) -> HaskellModule
toHaskellModule idecl = HaskellModule name qualifier isImplicit hiding importedAs specifically
where idecl' = SrcLoc.unLoc idecl
name = showSDoc tdflags (ppr $ GHC.ideclName idecl')
isImplicit = GHC.ideclImplicit idecl'
qualifier = unpackFS <$> GHC.ideclPkgQual idecl'
hiding = map removeBrackets $ (catMaybes . parseHiding . GHC.ideclHiding) idecl'
importedAs = (showSDoc tdflags . ppr) <$> ideclAs idecl'
specifically = map removeBrackets $ (parseSpecifically . GHC.ideclHiding) idecl'
removeBrackets :: [a] -> [a]
removeBrackets [] = []
removeBrackets x = (init . tail) x
grabNames :: GHC.Located (GHC.IE GHC.RdrName) -> String
grabNames loc = showSDoc tdflags (ppr names)
where names = GHC.ieNames $ SrcLoc.unLoc loc
parseHiding :: Maybe (Bool, [Located (IE RdrName)]) -> [Maybe String]
parseHiding Nothing = [Nothing]
parseHiding (Just (False, _)) = []
parseHiding (Just (True, h)) = map (Just . grabNames) h
parseSpecifically :: Maybe (Bool, [Located (IE RdrName)]) -> [String]
parseSpecifically (Just (False, h)) = map grabNames h
parseSpecifically _ = []
lookupSymbol :: GhcOptions -> FilePath -> String -> String -> [String] -> IO [(Name, [GlobalRdrElt])]
lookupSymbol ghcopts targetFile targetModuleName qualifiedSymbol importList =
runGhc (Just libdir) $ do
_ <- getSessionDynFlags >>= setDynamicFlags ghcopts
target <- guessTarget targetFile Nothing
setTargets [target]
_ <- load LoadAllTargets
(setContext $ map (IIDecl . simpleImportDecl . mkModuleName) (targetModuleName:importList))
`gcatch` (\(_ :: SourceError) -> do GhcMonad.liftIO $ putStrLn "lookupSymbol: setContext failed with a SourceError, trying to continue anyway..."
setContext $ map (IIDecl . simpleImportDecl . mkModuleName) importList)
`gcatch` (\(_ :: GhcApiError) -> do GhcMonad.liftIO $ putStrLn "lookupSymbol: setContext failed with a GhcApiError, trying to continue anyway..."
setContext $ map (IIDecl . simpleImportDecl . mkModuleName) importList)
`gcatch` (\(_ :: SomeException) -> do GhcMonad.liftIO $ putStrLn "lookupSymbol: setContext failed with a SomeException, trying to continue anyway..."
setContext $ map (IIDecl . simpleImportDecl . mkModuleName) importList)
modSummary <- getModSummary $ mkModuleName targetModuleName :: Ghc ModSummary
p <- parseModule modSummary :: Ghc ParsedModule
t <- typecheckModule p :: Ghc TypecheckedModule
d <- desugarModule t :: Ghc DesugaredModule
let guts = coreModule d :: ModGuts
gre = HscTypes.mg_rdr_env guts :: GlobalRdrEnv
names <- parseName qualifiedSymbol
let occNames = map nameOccName names :: [OccName]
occNamesLookups = map (lookupGlobalRdrEnv gre) occNames :: [[GlobalRdrElt]]
return $ zip names occNamesLookups
symbolImportedFrom :: GlobalRdrElt -> [ModuleName]
symbolImportedFrom occNameLookup = map importSpecModule whys
where prov = gre_prov occNameLookup :: Provenance
Imported (whys :: [ImportSpec]) = prov
separateBy :: Eq a => a -> [a] -> [[a]]
separateBy chr = unfoldr sep' where
sep' [] = Nothing
sep' l = Just . fmap (drop 1) . break (==chr) $ l
postfixMatch :: Symbol -> QualifiedName -> Bool
postfixMatch originalSymbol qName = endTerm `isSuffixOf` qName
where endTerm = last $ separateBy '.' originalSymbol
moduleOfQualifiedName :: QualifiedName -> Maybe String
moduleOfQualifiedName qn = if null bits
then Nothing
else Just $ intercalate "." bits
where bits = reverse $ drop 1 $ reverse $ separateBy '.' qn
qualifiedName :: GhcOptions -> FilePath -> String -> Int -> Int -> [String] -> IO [String]
qualifiedName ghcopts targetFile targetModuleName lineNr colNr importList =
runGhc (Just libdir) $ do
_ <- getSessionDynFlags >>= setDynamicFlags ghcopts
target <- guessTarget targetFile Nothing
setTargets [target]
_ <- load LoadAllTargets
(setContext $ map (IIDecl . simpleImportDecl . mkModuleName) (targetModuleName:importList))
`gcatch` (\(_ :: SourceError) -> GhcMonad.liftIO $ putStrLn "qualifiedName: setContext failed with a SourceError, trying to continue anyway...")
`gcatch` (\(_ :: GhcApiError) -> GhcMonad.liftIO $ putStrLn "qualifiedName: setContext failed with a GhcApiError, trying to continue anyway...")
`gcatch` (\(_ :: SomeException) -> GhcMonad.liftIO $ putStrLn "qualifiedName: setContext failed with a SomeException, trying to continue anyway...")
modSummary <- getModSummary $ mkModuleName targetModuleName :: Ghc ModSummary
p <- parseModule modSummary :: Ghc ParsedModule
t <- typecheckModule p :: Ghc TypecheckedModule
let TypecheckedModule{tm_typechecked_source = tcs} = t
bs = listifySpans tcs (lineNr, colNr) :: [LHsBind Id]
es = listifySpans tcs (lineNr, colNr) :: [LHsExpr Id]
ps = listifySpans tcs (lineNr, colNr) :: [LPat Id]
let foo x = showSDoc tdflags $ ppr x
bs' = map foo bs
es' = map foo es
ps' = map foo ps
return $ bs' ++ es' ++ ps'
readRestOfHandle :: Handle -> IO String
readRestOfHandle h = do
ineof <- hIsEOF h
if ineof
then return ""
else hGetContents h
optsForGhcPkg :: [String] -> [String]
optsForGhcPkg [] = []
optsForGhcPkg ("-no-user-package-db":rest) = "--no-user-package-db" : optsForGhcPkg rest
optsForGhcPkg ("-package-db":pd:rest) = ("--package-db" ++ "=" ++ pd) : optsForGhcPkg rest
optsForGhcPkg ("-package-conf":pc:rest) = ("--package-conf" ++ "=" ++ pc) : optsForGhcPkg rest
optsForGhcPkg ("-no-user-package-conf":rest) = "--no-user-package-conf" : optsForGhcPkg rest
optsForGhcPkg (_:rest) = optsForGhcPkg rest
ghcPkgFindModule :: GhcPkgOptions -> String -> IO (Maybe String)
ghcPkgFindModule (GhcPkgOptions extraGHCPkgOpts) m = do
gopts <- getGhcOptionsViaCabalReplOrEmpty
let opts = ["find-module", m, "--simple-output"] ++ ["--global", "--user"] ++ optsForGhcPkg gopts ++ extraGHCPkgOpts
putStrLn $ "ghc-pkg " ++ show opts
(_, Just hout, Just herr, _) <- createProcess (proc "ghc-pkg" opts){ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe
}
output <- readRestOfHandle hout
err <- readRestOfHandle herr
putStrLn $ "ghcPkgFindModule stdout: " ++ show output
putStrLn $ "ghcPkgFindModule stderr: " ++ show err
return $ join $ Safe.lastMay <$> words <$> (Safe.lastMay . lines) output
ghcPkgHaddockUrl :: GhcPkgOptions -> String -> IO (Maybe String)
ghcPkgHaddockUrl (GhcPkgOptions extraGHCPkgOpts) p = do
gopts <- getGhcOptionsViaCabalReplOrEmpty
let opts = ["field", p, "haddock-html"] ++ ["--global", "--user"] ++ optsForGhcPkg gopts ++ extraGHCPkgOpts
putStrLn $ "ghc-pkg "++ show opts
(_, Just hout, _, _) <- createProcess (proc "ghc-pkg" opts){ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe
}
line <- (reverse . dropWhile (== '\n') . reverse) <$> readRestOfHandle hout
return $ Safe.lastMay $ words line
moduleNameToHtmlFile :: String -> String
moduleNameToHtmlFile m = map f m ++ ".html"
where f :: Char -> Char
f '.' = '-'
f c = c
expandMatchingAsImport :: QualifiedName -> [HaskellModule] -> Maybe QualifiedName
expandMatchingAsImport symbol hmodules = case x of (Just (h, Just cp)) -> Just $ modName h ++ drop (length cp) symbol
_ -> Nothing
where x = Safe.headMay $ filter (isJust . snd) $ zip hmodules (map (cmpMod symbol) hmodules)
cmpMod s (HaskellModule _ _ _ _ (Just impAs) _) = if impAs `isPrefixOf` s
then Just $ commonPrefix s impAs
else Nothing
cmpMod _ _ = Nothing
commonPrefix :: Eq a => [a] -> [a] -> [a]
commonPrefix a b = map fst (takeWhile (uncurry (==)) (zip a b))
specificallyMatches :: Symbol -> [HaskellModule] -> [HaskellModule]
specificallyMatches symbol = filter (\h -> symbol `elem` modSpecifically h)
toHackageUrl :: FilePath -> String -> String -> String
toHackageUrl filepath package modulename = "https://hackage.haskell.org/package/" ++ package ++ "/" ++ "docs/" ++ modulename''
where filepath' = map repl filepath
modulename' = head $ separateBy '.' $ head $ separateBy '-' modulename
modulename'' = drop (fromJust $ substringP modulename' filepath') filepath'
repl :: Char -> Char
repl '\\' = '/'
repl c = c
substringP :: String -> String -> Maybe Int
substringP _ [] = Nothing
substringP sub str = if sub `isPrefixOf` str then Just 0 else (+1) <$> substringP sub (tail str)
bestPrefixMatches :: Name -> [GlobalRdrElt] -> [String]
bestPrefixMatches name lookUp = x''
where name' = showSDoc tdflags $ ppr name
name'' = fromJust $ moduleOfQualifiedName name'
x = concatMap symbolImportedFrom lookUp
x' = map (showSDoc tdflags . ppr) x
x'' = filter (name'' `isPrefixOf`) x'
findHaddockModule :: QualifiedName -> [HaskellModule] -> GhcPkgOptions -> (Name, [GlobalRdrElt]) -> IO (Maybe String, Maybe String, Maybe String, Maybe String)
findHaddockModule symbol'' smatches ghcpkgOpts (name, lookUp) = do
putStrLn $ "name: " ++ showSDoc tdflags (ppr name)
let definedIn = nameModule name
bpms = bestPrefixMatches name lookUp
importedFrom = if null smatches
then if null bpms then Safe.headMay $ map (showSDoc tdflags . ppr) $ concatMap symbolImportedFrom lookUp
else Safe.headMay bpms :: Maybe String
else (Just . (showSDoc tdflags . ppr) . mkModuleName . fromJust . moduleOfQualifiedName) symbol''
putStrLn $ "definedIn: " ++ showSDoc tdflags (ppr definedIn)
putStrLn $ "bpms: " ++ show bpms
putStrLn $ "concat $ map symbolImportedFrom lookUp: " ++ showSDoc tdflags (ppr $ concatMap symbolImportedFrom lookUp)
putStrLn $ "importedFrom: " ++ show importedFrom
foundModule <- maybe (return Nothing) (ghcPkgFindModule ghcpkgOpts) importedFrom
putStrLn $ "ghcPkgFindModule result: " ++ show foundModule
let base = moduleNameToHtmlFile <$> importedFrom
putStrLn $ "base: : " ++ show base
haddock <- maybe (return Nothing) (ghcPkgHaddockUrl ghcpkgOpts) foundModule
putStrLn $ "haddock: " ++ show haddock
putStrLn $ "foundModule: " ++ show foundModule
return (importedFrom, haddock, foundModule, base)
matchToUrl :: (Maybe String, Maybe String, Maybe String, Maybe String) -> IO String
matchToUrl (importedFrom, haddock, foundModule, base) = do
let importedFrom' = fromJust importedFrom
haddock' = fromJust haddock
foundModule' = fromJust foundModule
base' = fromJust base
f = haddock' </> base'
e <- doesFileExist f
if e then return $ "file://" ++ f
else do putStrLn $ "f: " ++ show f
putStrLn $ "foundModule: " ++ show foundModule'
return $ toHackageUrl f foundModule' (showSDoc tdflags (ppr importedFrom'))
guessHaddockUrl :: FilePath -> String -> Symbol -> Int -> Int -> GhcOptions -> GhcPkgOptions -> IO (Either String String)
guessHaddockUrl _targetFile targetModule symbol lineNr colNr (GhcOptions ghcOpts0) ghcpkgOptions = do
cradle <- findCradle
let currentDir = cradleCurrentDir cradle
workDir = cradleRootDir cradle
setCurrentDirectory workDir
let targetFile = currentDir </> _targetFile
putStrLn $ "targetFile: " ++ targetFile
putStrLn $ "targetModule: " ++ targetModule
putStrLn $ "symbol: " ++ show symbol
putStrLn $ "line nr: " ++ show lineNr
putStrLn $ "col nr: " ++ show colNr
putStrLn $ "ghcOpts0: " ++ show ghcOpts0
putStrLn $ "ghcpkgOptions: " ++ show ghcpkgOptions
textualImports <- getTextualImports (GhcOptions ghcOpts0) targetFile targetModule
let haskellModuleNames = map (modName . toHaskellModule) textualImports
putStrLn $ "haskellModuleNames: " ++ show haskellModuleNames
qnames <- filter (not . (' ' `elem`)) <$> qualifiedName (GhcOptions ghcOpts0) targetFile targetModule lineNr colNr haskellModuleNames
putStrLn $ "qualified names: " ++ show qnames
let matchingAsImport = expandMatchingAsImport symbol (map toHaskellModule textualImports)
putStrLn $ "matchingAsImport: " ++ show matchingAsImport
let postMatches = filter (postfixMatch symbol) qnames :: [String]
symbol' = fromMaybe (if null postMatches then symbol else minimumBy (compare `on` length) postMatches) matchingAsImport
putStrLn $ "postMatches: " ++ show postMatches
putStrLn $ "symbol': " ++ symbol'
let maybeExtraModule = moduleOfQualifiedName symbol'
haskellModuleNames' = if symbol == symbol' then haskellModuleNames else haskellModuleNames ++ [fromJust maybeExtraModule]
putStrLn $ "maybeExtraModule: " ++ show maybeExtraModule
putStrLn $ "haskellModuleNames': " ++ show haskellModuleNames'
let smatches = specificallyMatches symbol (map toHaskellModule textualImports)
putStrLn $ "smatches: " ++ show smatches
let symbol'' = if null smatches
then symbol'
else modName (head smatches) ++ "." ++ symbol
putStrLn $ "symbol'': " ++ symbol''
let allJust (a, b, c, d) = isJust a && isJust b && isJust c && isJust d
final1 <- lookupSymbol (GhcOptions ghcOpts0) targetFile targetModule symbol'' haskellModuleNames'
final2 <- filter allJust <$> mapM (findHaddockModule symbol'' smatches ghcpkgOptions) final1
final3 <- mapM matchToUrl final2
return (if null final3 then Left "No matches found."
else Right $ head final3)
haddockUrl :: Options -> FilePath -> String -> String -> Int -> Int -> IO String
haddockUrl opt file modstr symbol lineNr colNr = do
let ghcopts = GhcOptions $ ghcOpts opt
let ghcpkgopts = GhcPkgOptions $ ghcPkgOpts opt
res <- (guessHaddockUrl file modstr symbol lineNr colNr ghcopts ghcpkgopts)
`gcatch` (\(_ :: SourceError) -> return $ Left "guessHaddockUrl failed with a SourceError")
`gcatch` (\(_ :: GhcApiError) -> return $ Left "guessHaddockUrl failed with a GhcApiError")
`gcatch` (\(_ :: SomeException) -> return $ Left "guessHaddockUrl failed with a SomeException")
return $ case res of Right x -> "SUCCESS: " ++ x ++ "\n"
Left err -> "FAIL: " ++ show err ++ "\n"