ghc-mod/Language/Haskell/GhcMod/Find.hs

191 lines
6.0 KiB
Haskell
Raw Normal View History

2014-07-18 06:13:30 +00:00
{-# LANGUAGE CPP, BangPatterns #-}
2014-04-24 08:02:50 +00:00
module Language.Haskell.GhcMod.Find
#ifndef SPEC
(
Symbol
, SymbolDb
2014-07-17 05:04:28 +00:00
, loadSymbolDb
, lookupSymbol
, dumpSymbol
, findSymbol
2014-07-18 06:13:30 +00:00
, lookupSym
)
#endif
where
2014-04-24 08:02:50 +00:00
import Config (cProjectVersion,cTargetPlatformString)
import Control.Applicative ((<$>))
2014-07-17 03:37:38 +00:00
import Control.Exception (handle, SomeException(..))
import Control.Monad (when, void)
2014-07-22 20:54:18 +00:00
import Control.Monad.Error.Class
import CoreMonad (liftIO)
2014-04-24 08:02:50 +00:00
import Data.Function (on)
import Data.List (groupBy, sort)
import Data.List.Split (splitOn)
2014-04-24 08:02:50 +00:00
import Data.Maybe (fromMaybe)
import DynFlags (DynFlags(..), systemPackageConfig)
2014-07-22 20:54:18 +00:00
import Exception (handleIO)
2014-04-24 08:02:50 +00:00
import qualified GHC as G
2014-05-11 22:40:00 +00:00
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Monad
2014-07-17 14:17:17 +00:00
import Language.Haskell.GhcMod.Utils
2014-04-24 12:08:45 +00:00
import Language.Haskell.GhcMod.Types
import Name (getOccString)
import System.Directory (doesDirectoryExist, getAppUserDataDirectory, doesFileExist, getModificationTime)
2014-07-19 02:50:12 +00:00
import System.FilePath ((</>), takeDirectory)
import System.IO
import System.Environment
2014-04-24 08:02:50 +00:00
#ifndef MIN_VERSION_containers
#define MIN_VERSION_containers(x,y,z) 1
#endif
#if MIN_VERSION_containers(0,5,0)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
#else
import Data.Map (Map)
import qualified Data.Map as M
#endif
----------------------------------------------------------------
2014-07-17 05:04:28 +00:00
-- | Type of function and operation names.
2014-04-24 08:02:50 +00:00
type Symbol = String
2014-07-17 05:04:28 +00:00
-- | Database from 'Symbol' to \['ModuleString'\].
2014-07-22 20:54:18 +00:00
newtype SymbolDb = SymbolDb (Map Symbol [ModuleString]) deriving (Show)
----------------------------------------------------------------
symbolCache :: String
symbolCache = "ghc-mod.cache"
packageCache :: String
packageCache = "package.cache"
packageConfDir :: String
packageConfDir = "package.conf.d"
----------------------------------------------------------------
2014-04-24 08:02:50 +00:00
2014-07-18 06:42:05 +00:00
-- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\]
-- which will be concatenated. 'loadSymbolDb' is called internally.
findSymbol :: IOish m => Symbol -> GhcModT m String
2014-07-18 06:13:30 +00:00
findSymbol sym = liftIO loadSymbolDb >>= lookupSymbol sym
2014-07-17 05:04:28 +00:00
-- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\]
-- which will be concatenated.
2014-07-18 06:13:30 +00:00
lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m String
lookupSymbol sym db = convert' $ lookupSym sym db
lookupSym :: Symbol -> SymbolDb -> [ModuleString]
lookupSym sym (SymbolDb db) = fromMaybe [] $ M.lookup sym db
---------------------------------------------------------------
2014-07-17 05:04:28 +00:00
-- | Loading a file and creates 'SymbolDb'.
loadSymbolDb :: IO SymbolDb
loadSymbolDb = SymbolDb <$> readSymbolDb
2014-07-17 14:17:17 +00:00
ghcModExecutable :: IO FilePath
#ifndef SPEC
2014-07-19 02:50:12 +00:00
ghcModExecutable = do
dir <- getExecutablePath'
2014-07-19 02:50:12 +00:00
return $ dir </> "ghc-mod"
2014-07-17 14:17:17 +00:00
#else
2014-07-19 02:50:12 +00:00
ghcModExecutable = return "dist/build/ghc-mod/ghc-mod"
2014-07-17 14:17:17 +00:00
#endif
where
getExecutablePath' :: IO FilePath
# if __GLASGOW_HASKELL__ >= 706
getExecutablePath' = takeDirectory <$> getExecutablePath
# else
getExecutablePath' = return ""
# endif
2014-07-17 14:17:17 +00:00
readSymbolDb :: IO (Map Symbol [ModuleString])
2014-07-17 05:04:28 +00:00
readSymbolDb = handle (\(SomeException _) -> return M.empty) $ do
2014-07-17 14:17:17 +00:00
ghcMod <- ghcModExecutable
file <- chop <$> readProcess' ghcMod ["dumpsym"]
2014-07-17 03:37:38 +00:00
M.fromAscList . map conv . lines <$> readFile file
2014-04-24 08:02:50 +00:00
where
conv :: String -> (Symbol,[ModuleString])
conv = read
chop "" = ""
chop xs = init xs
----------------------------------------------------------------
-- used 'ghc-mod dumpsym'
2014-07-22 20:54:18 +00:00
getSymbolCachePath :: IOish m => GhcModT m FilePath
getSymbolCachePath = do
u:_ <- filter (/= GlobalDb) . cradlePkgDbStack <$> cradle
Just db <- (liftIO . flip resolvePackageDb u) =<< G.getSessionDynFlags
return db
`catchError` const (fail "Couldn't find non-global package database for symbol cache")
2014-07-17 05:04:28 +00:00
-- | Dumping a set of ('Symbol',\['ModuleString'\]) to a file
-- if the file does not exist or is invalid.
-- The file name is printed.
dumpSymbol :: IOish m => GhcModT m String
dumpSymbol = do
2014-07-22 20:54:18 +00:00
dir <- getSymbolCachePath
let cache = dir </> symbolCache
pkgdb = dir </> packageCache
create <- liftIO $ cache `isNewerThan` pkgdb
when create $ (liftIO . writeSymbolCache cache) =<< getSymbolTable
return $ unlines [cache]
writeSymbolCache :: FilePath
-> [(Symbol,[ModuleString])]
-> IO ()
writeSymbolCache cache sm = do
void . withFile cache WriteMode $ \hdl ->
mapM (hPrint hdl) sm
isNewerThan :: FilePath -> FilePath -> IO Bool
isNewerThan ref file = do
exist <- doesFileExist ref
if not exist then
return True
else do
2014-07-22 20:54:18 +00:00
tRef <- getModificationTime ref
tFile <- getModificationTime file
return $ tRef <= tFile -- including equal just in case
2014-05-14 16:54:56 +00:00
-- | Browsing all functions in all system/user modules.
2014-07-22 20:54:18 +00:00
getSymbolTable :: IOish m => GhcModT m [(Symbol,[ModuleString])]
getSymbolTable = do
ms <- G.packageDbModules True
let ns = map (G.moduleNameString . G.moduleName) ms
is <- mapM G.getModuleInfo ms
let symbols = concatMap toNameModule (zip is ns)
return $ uniquefy symbols
toNameModule :: (Maybe G.ModuleInfo,ModuleString) -> [(Symbol,ModuleString)]
toNameModule (Nothing,_) = []
2014-07-22 20:54:18 +00:00
toNameModule (Just inf,mdlname) =
map (\name -> (getOccString name, mdlname)) names
where
names = G.modInfoExports inf
uniquefy :: [(Symbol,ModuleString)] -> [(Symbol,[ModuleString])]
uniquefy = map tieup . groupBy ((==) `on` fst) . sort
where
tieup x = (head (map fst x), map snd x)
--- Copied from ghc module `Packages' unfortunately it's not exported :/
resolvePackageDb :: DynFlags -> GhcPkgDb -> IO (Maybe FilePath)
resolvePackageDb df GlobalDb = return $ Just (systemPackageConfig df)
resolvePackageDb _ (PackageDb name) = return $ Just name
resolvePackageDb _ UserDb = handleIO (\_ -> return Nothing) $ do
appdir <- getAppUserDataDirectory "ghc"
let dir = appdir </> (target_arch ++ '-':target_os ++ '-':cProjectVersion)
pkgconf = dir </> packageConfDir
exist <- doesDirectoryExist pkgconf
return $ if exist then Just pkgconf else Nothing
where
[target_arch,_,target_os] = splitOn "-" cTargetPlatformString