Merge branch 'btr-find' of https://github.com/atom-haskell/ghc-mod into release-5.5.0.0

This commit is contained in:
Daniel Gröber 2016-01-09 22:17:49 +01:00
commit 8b5bd1ae2b
10 changed files with 92 additions and 87 deletions

View File

@ -1,4 +1,4 @@
{-# LANGUAGE CPP, BangPatterns, DoAndIfThenElse #-} {-# LANGUAGE CPP, DeriveGeneric #-}
module Language.Haskell.GhcMod.Find module Language.Haskell.GhcMod.Find
#ifndef SPEC #ifndef SPEC
@ -22,7 +22,6 @@ import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Gap import Language.Haskell.GhcMod.Gap
import Language.Haskell.GhcMod.Monad import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Output import Language.Haskell.GhcMod.Output
import Language.Haskell.GhcMod.PathsAndFiles
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Utils import Language.Haskell.GhcMod.Utils
import Language.Haskell.GhcMod.World import Language.Haskell.GhcMod.World
@ -36,14 +35,15 @@ import Control.Applicative
import Control.Monad import Control.Monad
import Control.Monad.Trans.Control import Control.Monad.Trans.Control
import Control.Concurrent import Control.Concurrent
import Control.DeepSeq
import Data.Function import Data.Function
import Data.List import Data.List
import qualified Data.ByteString.Lazy as BS
import Data.Binary
import GHC.Generics (Generic)
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as M import qualified Data.Map as M
import System.Directory
import System.Directory.ModTime import System.Directory.ModTime
import System.FilePath ((</>))
import System.IO
import Prelude import Prelude
---------------------------------------------------------------- ----------------------------------------------------------------
@ -53,21 +53,22 @@ type Symbol = String
-- | Database from 'Symbol' to \['ModuleString'\]. -- | Database from 'Symbol' to \['ModuleString'\].
data SymbolDb = SymbolDb data SymbolDb = SymbolDb
{ table :: Map Symbol [ModuleString] { table :: Map Symbol [ModuleString]
, symbolDbCachePath :: FilePath , timestamp :: ModTime
} deriving (Show) } deriving (Generic)
instance Binary SymbolDb
instance NFData SymbolDb
isOutdated :: IOish m => SymbolDb -> GhcModT m Bool isOutdated :: IOish m => SymbolDb -> GhcModT m Bool
isOutdated db = isOutdated db =
(liftIO . isOlderThan (symbolDbCachePath db)) =<< timedPackageCaches isOlderThan (timestamp db) <$> timedPackageCaches
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\] -- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\]
-- which will be concatenated. 'loadSymbolDb' is called internally. -- which will be concatenated. 'loadSymbolDb' is called internally.
findSymbol :: IOish m => Symbol -> GhcModT m String findSymbol :: IOish m => Symbol -> GhcModT m String
findSymbol sym = do findSymbol sym = loadSymbolDb >>= lookupSymbol sym
tmpdir <- cradleTempDir <$> cradle
loadSymbolDb tmpdir >>= lookupSymbol sym
-- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\] -- | Looking up 'SymbolDb' with 'Symbol' to \['ModuleString'\]
-- which will be concatenated. -- which will be concatenated.
@ -80,57 +81,31 @@ lookupSym sym db = M.findWithDefault [] sym $ table db
--------------------------------------------------------------- ---------------------------------------------------------------
-- | Loading a file and creates 'SymbolDb'. -- | Loading a file and creates 'SymbolDb'.
loadSymbolDb :: IOish m => FilePath -> GhcModT m SymbolDb loadSymbolDb :: IOish m => GhcModT m SymbolDb
loadSymbolDb dir = do loadSymbolDb = do
ghcMod <- liftIO ghcModExecutable ghcMod <- liftIO ghcModExecutable
readProc <- gmReadProcess readProc <- gmReadProcess'
file <- liftIO $ chop <$> readProc ghcMod ["dumpsym", dir] "" out <- liftIO $ readProc ghcMod ["--verbose", "error", "dumpsym"] ""
!db <- M.fromAscList . map conv . lines <$> liftIO (readFile file) return $!! decode out
return $ SymbolDb
{ table = db
, symbolDbCachePath = file
}
where
conv :: String -> (Symbol, [ModuleString])
conv = read
chop :: String -> String
chop "" = ""
chop xs = init xs
---------------------------------------------------------------- ----------------------------------------------------------------
-- used 'ghc-mod dumpsym' -- used 'ghc-mod dumpsym'
-- | Dumping a set of ('Symbol',\['ModuleString'\]) to a file -- | Dumps a 'Binary' representation of 'SymbolDb' to stdout
-- if the file does not exist or is invalid. dumpSymbol :: IOish m => GhcModT m ()
-- The file name is printed. dumpSymbol = do
ts <- liftIO getCurrentModTime
dumpSymbol :: IOish m => FilePath -> GhcModT m String st <- runGmPkgGhc getGlobalSymbolTable
dumpSymbol dir = do liftIO . BS.putStr $ encode SymbolDb {
create <- (liftIO . isOlderThan cache) =<< timedPackageCaches table = M.fromAscList st
runGmPkgGhc $ do , timestamp = ts
when create $ }
liftIO . writeSymbolCache cache =<< getGlobalSymbolTable
return $ unlines [cache]
where
cache = dir </> symbolCacheFile
writeSymbolCache :: FilePath
-> [(Symbol, [ModuleString])]
-> IO ()
writeSymbolCache cache sm =
void . withFile cache WriteMode $ \hdl ->
mapM (hPrint hdl) sm
-- | Check whether given file is older than any file from the given set. -- | Check whether given file is older than any file from the given set.
-- Returns True if given file does not exist. -- Returns True if given file does not exist.
isOlderThan :: FilePath -> [TimedFile] -> IO Bool isOlderThan :: ModTime -> [TimedFile] -> Bool
isOlderThan cache files = do isOlderThan tCache files =
exist <- doesFileExist cache any (tCache <=) $ map tfTime files -- including equal just in case
if not exist
then return True
else do
tCache <- getModTime cache
return $ any (tCache <=) $ map tfTime files -- including equal just in case
-- | Browsing all functions in all system modules. -- | Browsing all functions in all system modules.
getGlobalSymbolTable :: LightGhc [(Symbol, [ModuleString])] getGlobalSymbolTable :: LightGhc [(Symbol, [ModuleString])]
@ -158,30 +133,29 @@ collectModules = map tieup . groupBy ((==) `on` fst) . sort
---------------------------------------------------------------- ----------------------------------------------------------------
data AsyncSymbolDb = AsyncSymbolDb FilePath (MVar (Either SomeException SymbolDb)) data AsyncSymbolDb = AsyncSymbolDb (MVar (Either SomeException SymbolDb))
asyncLoadSymbolDb :: IOish m asyncLoadSymbolDb :: IOish m
=> FilePath => MVar (Either SomeException SymbolDb)
-> MVar (Either SomeException SymbolDb)
-> GhcModT m () -> GhcModT m ()
asyncLoadSymbolDb tmpdir mv = void $ asyncLoadSymbolDb mv = void $
liftBaseWith $ \run -> forkIO $ void $ run $ do liftBaseWith $ \run -> forkIO $ void $ run $ do
edb <- gtry $ loadSymbolDb tmpdir edb <- gtry loadSymbolDb
liftIO $ putMVar mv edb liftIO $ putMVar mv edb
newAsyncSymbolDb :: IOish m => FilePath -> GhcModT m AsyncSymbolDb newAsyncSymbolDb :: IOish m => GhcModT m AsyncSymbolDb
newAsyncSymbolDb tmpdir = do newAsyncSymbolDb = do
mv <- liftIO newEmptyMVar mv <- liftIO newEmptyMVar
asyncLoadSymbolDb tmpdir mv asyncLoadSymbolDb mv
return $ AsyncSymbolDb tmpdir mv return $ AsyncSymbolDb mv
getAsyncSymbolDb :: forall m. IOish m => AsyncSymbolDb -> GhcModT m SymbolDb getAsyncSymbolDb :: forall m. IOish m => AsyncSymbolDb -> GhcModT m SymbolDb
getAsyncSymbolDb (AsyncSymbolDb tmpdir mv) = do getAsyncSymbolDb (AsyncSymbolDb mv) = do
db <- liftIO $ handleEx <$> takeMVar mv db <- liftIO $ handleEx <$> takeMVar mv
outdated <- isOutdated db outdated <- isOutdated db
if outdated if outdated
then do then do
asyncLoadSymbolDb tmpdir mv asyncLoadSymbolDb mv
liftIO $ handleEx <$> readMVar mv liftIO $ handleEx <$> readMVar mv
else do else do
liftIO $ putMVar mv $ Right db liftIO $ putMVar mv $ Right db

View File

@ -101,6 +101,11 @@ import Module
import qualified Data.IntSet as I (IntSet, empty) import qualified Data.IntSet as I (IntSet, empty)
#endif #endif
#if __GLASGOW_HASKELL__ < 706
import Control.DeepSeq (NFData(rnf))
import Data.ByteString.Lazy.Internal (ByteString(..))
#endif
import Bag import Bag
import Lexer as L import Lexer as L
import Parser import Parser
@ -564,3 +569,9 @@ mkErrStyle' = Outputable.mkErrStyle
#else #else
mkErrStyle' _ = Outputable.mkErrStyle mkErrStyle' _ = Outputable.mkErrStyle
#endif #endif
#if __GLASGOW_HASKELL__ < 706
instance NFData ByteString where
rnf Empty = ()
rnf (Chunk _ b) = rnf b
#endif

View File

@ -17,6 +17,7 @@
-- Derived from process:System.Process -- Derived from process:System.Process
-- Copyright (c) The University of Glasgow 2004-2008 -- Copyright (c) The University of Glasgow 2004-2008
{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.Output ( module Language.Haskell.GhcMod.Output (
gmPutStr gmPutStr
, gmErrStr , gmErrStr
@ -27,12 +28,15 @@ module Language.Haskell.GhcMod.Output (
, gmErrStrIO , gmErrStrIO
, gmReadProcess , gmReadProcess
, gmReadProcess'
, stdoutGateway , stdoutGateway
, flushStdoutGateway , flushStdoutGateway
) where ) where
import Data.List import Data.List
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as BS
import qualified Data.Label as L import qualified Data.Label as L
import qualified Data.Label.Base as LB import qualified Data.Label.Base as LB
import System.IO import System.IO
@ -51,6 +55,16 @@ import Prelude
import Language.Haskell.GhcMod.Types hiding (LineSeparator, MonadIO(..)) import Language.Haskell.GhcMod.Types hiding (LineSeparator, MonadIO(..))
import Language.Haskell.GhcMod.Monad.Types hiding (MonadIO(..)) import Language.Haskell.GhcMod.Monad.Types hiding (MonadIO(..))
import Language.Haskell.GhcMod.Gap ()
class ProcessOutput a where
hGetContents' :: Handle -> IO a
instance ProcessOutput String where
hGetContents' = hGetContents
instance ProcessOutput ByteString where
hGetContents' = BS.hGetContents
outputFns :: (GmOut m, MonadIO m') outputFns :: (GmOut m, MonadIO m')
=> m (String -> m' (), String -> m' ()) => m (String -> m' (), String -> m' ())
@ -108,6 +122,9 @@ gmReadProcess = do
Nothing -> Nothing ->
return $ readProcess return $ readProcess
gmReadProcess' :: GmOut m => m (FilePath -> [String] -> String -> IO ByteString)
gmReadProcess' = readProcessStderrChan
flushStdoutGateway :: Chan (Either (MVar ()) (GmStream, String)) -> IO () flushStdoutGateway :: Chan (Either (MVar ()) (GmStream, String)) -> IO ()
flushStdoutGateway c = do flushStdoutGateway c = do
mv <- newEmptyMVar mv <- newEmptyMVar
@ -175,17 +192,14 @@ zoom l (StateT a) =
return (a', L.set l s' f) return (a', L.set l s' f)
readProcessStderrChan :: readProcessStderrChan ::
GmOut m => m (FilePath -> [String] -> String -> IO String) (GmOut m, ProcessOutput a, NFData a) => m (FilePath -> [String] -> String -> IO a)
readProcessStderrChan = do readProcessStderrChan = do
(_, e :: String -> IO ()) <- outputFns (_, e :: String -> IO ()) <- outputFns
return $ readProcessStderrChan' e return $ readProcessStderrChan' e
readProcessStderrChan' :: readProcessStderrChan' :: (ProcessOutput a, NFData a) =>
(String -> IO ()) -> FilePath -> [String] -> String -> IO String (String -> IO ()) -> FilePath -> [String] -> String -> IO a
readProcessStderrChan' pute = go pute readProcessStderrChan' putErr exe args input = do
where
go :: (String -> IO ()) -> FilePath -> [String] -> String -> IO String
go putErr exe args input = do
let cp = (proc exe args) { let cp = (proc exe args) {
std_out = CreatePipe std_out = CreatePipe
, std_err = CreatePipe , std_err = CreatePipe
@ -195,7 +209,7 @@ readProcessStderrChan' pute = go pute
_ <- forkIO $ reader e _ <- forkIO $ reader e
output <- hGetContents o output <- hGetContents' o
withForkWait (evaluate $ rnf output) $ \waitOut -> do withForkWait (evaluate $ rnf output) $ \waitOut -> do
-- now write any input -- now write any input

View File

@ -1,5 +1,6 @@
{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveGeneric, RankNTypes, {-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveGeneric, RankNTypes,
StandaloneDeriving, DefaultSignatures, FlexibleInstances, TemplateHaskell #-} StandaloneDeriving, DefaultSignatures, FlexibleInstances, TemplateHaskell,
GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-} {-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
module Language.Haskell.GhcMod.Types ( module Language.Haskell.GhcMod.Types (
module Language.Haskell.GhcMod.Types module Language.Haskell.GhcMod.Types
@ -15,6 +16,7 @@ import Control.Exception (Exception)
import Control.Applicative import Control.Applicative
import Control.Concurrent import Control.Concurrent
import Control.Monad import Control.Monad
import Control.DeepSeq
import Data.Binary import Data.Binary
import Data.Binary.Generic import Data.Binary.Generic
import Data.Map (Map) import Data.Map (Map)
@ -232,7 +234,7 @@ newtype Expression = Expression { getExpression :: String }
-- | Module name. -- | Module name.
newtype ModuleString = ModuleString { getModuleString :: String } newtype ModuleString = ModuleString { getModuleString :: String }
deriving (Show, Read, Eq, Ord) deriving (Show, Eq, Ord, Binary, NFData)
data GmLogLevel = data GmLogLevel =
GmSilent GmSilent

View File

@ -13,10 +13,11 @@
-- --
-- You should have received a copy of the GNU Affero General Public License -- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>. -- along with this program. If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP, GeneralizedNewtypeDeriving #-}
module System.Directory.ModTime where module System.Directory.ModTime where
import Control.Applicative import Control.Applicative
import Control.DeepSeq
import Data.Binary import Data.Binary
#if MIN_VERSION_directory(1,2,0) #if MIN_VERSION_directory(1,2,0)
import Data.Time (UTCTime(..), Day(..), getCurrentTime) import Data.Time (UTCTime(..), Day(..), getCurrentTime)
@ -29,7 +30,7 @@ import Prelude
#if MIN_VERSION_directory(1,2,0) #if MIN_VERSION_directory(1,2,0)
newtype ModTime = ModTime UTCTime newtype ModTime = ModTime UTCTime
deriving (Eq, Ord) deriving (Eq, Ord, NFData)
getCurrentModTime = ModTime <$> getCurrentTime getCurrentModTime = ModTime <$> getCurrentTime
instance Binary ModTime where instance Binary ModTime where
@ -41,7 +42,7 @@ instance Binary ModTime where
#else #else
newtype ModTime = ModTime ClockTime newtype ModTime = ModTime ClockTime
deriving (Eq, Ord, Show) deriving (Eq, Ord)
getCurrentModTime = ModTime <$> getClockTime getCurrentModTime = ModTime <$> getClockTime
instance Binary ModTime where instance Binary ModTime where
@ -50,6 +51,10 @@ instance Binary ModTime where
get = get =
ModTime <$> (TOD <$> get <*> get) ModTime <$> (TOD <$> get <*> get)
instance NFData ModTime where
rnf (ModTime (TOD s ps)) =
s `seq` ps `seq` (ModTime $! TOD s ps) `seq` ()
#endif #endif
getCurrentModTime :: IO ModTime getCurrentModTime :: IO ModTime

View File

@ -231,6 +231,7 @@ Executable ghc-modi
HS-Source-Dirs: src, . HS-Source-Dirs: src, .
Build-Depends: base < 5 && >= 4.0 Build-Depends: base < 5 && >= 4.0
, binary < 0.8 && >= 0.5.1.0 , binary < 0.8 && >= 0.5.1.0
, deepseq < 1.5
, directory < 1.3 , directory < 1.3
, filepath < 1.5 , filepath < 1.5
, process < 1.3 , process < 1.3

View File

@ -49,8 +49,7 @@ progMain (globalOptions, commands) = runGmOutT globalOptions $
legacyInteractive :: IOish m => GhcModT m () legacyInteractive :: IOish m => GhcModT m ()
legacyInteractive = do legacyInteractive = do
prepareCabalHelper prepareCabalHelper
tmpdir <- cradleTempDir <$> cradle asyncSymbolDb <- newAsyncSymbolDb
asyncSymbolDb <- newAsyncSymbolDb tmpdir
world <- getCurrentWorld world <- getCurrentWorld
legacyInteractiveLoop asyncSymbolDb world legacyInteractiveLoop asyncSymbolDb world
@ -137,7 +136,7 @@ ghcCommands (CmdBoot) = boot
-- ghcCommands (CmdRoot) = undefined -- handled in wrapGhcCommands -- ghcCommands (CmdRoot) = undefined -- handled in wrapGhcCommands
ghcCommands (CmdLegacyInteractive) = legacyInteractive >> return "" ghcCommands (CmdLegacyInteractive) = legacyInteractive >> return ""
ghcCommands (CmdModules detail) = modules detail ghcCommands (CmdModules detail) = modules detail
ghcCommands (CmdDumpSym tmpdir) = dumpSymbol tmpdir ghcCommands (CmdDumpSym) = dumpSymbol >> return ""
ghcCommands (CmdFind symb) = findSymbol symb ghcCommands (CmdFind symb) = findSymbol symb
ghcCommands (CmdDoc m) = pkgDoc m ghcCommands (CmdDoc m) = pkgDoc m
ghcCommands (CmdLint opts file) = lint opts file ghcCommands (CmdLint opts file) = lint opts file

View File

@ -42,7 +42,7 @@ data GhcModCommands =
| CmdRoot | CmdRoot
| CmdLegacyInteractive | CmdLegacyInteractive
| CmdModules Bool | CmdModules Bool
| CmdDumpSym FilePath | CmdDumpSym
| CmdFind Symbol | CmdFind Symbol
| CmdDoc Module | CmdDoc Module
| CmdLint LintOpts FilePath | CmdLint LintOpts FilePath
@ -110,7 +110,7 @@ commands =
$$ info modulesArgSpec $$ info modulesArgSpec
$$ progDesc "List all visible modules" $$ progDesc "List all visible modules"
<> command "dumpsym" <> command "dumpsym"
$$ info dumpSymArgSpec idm $$ info (pure CmdDumpSym) idm
<> command "find" <> command "find"
$$ info findArgSpec $$ info findArgSpec
$$ progDesc "List all modules that define SYMBOL" $$ progDesc "List all modules that define SYMBOL"
@ -226,7 +226,7 @@ locArgSpec x = x
<*> argument int (metavar "COL") <*> argument int (metavar "COL")
) )
modulesArgSpec, dumpSymArgSpec, docArgSpec, findArgSpec, modulesArgSpec, docArgSpec, findArgSpec,
lintArgSpec, browseArgSpec, checkArgSpec, expandArgSpec, lintArgSpec, browseArgSpec, checkArgSpec, expandArgSpec,
infoArgSpec, typeArgSpec, autoArgSpec, splitArgSpec, infoArgSpec, typeArgSpec, autoArgSpec, splitArgSpec,
sigArgSpec, refineArgSpec, debugComponentArgSpec, sigArgSpec, refineArgSpec, debugComponentArgSpec,
@ -237,7 +237,6 @@ modulesArgSpec = CmdModules
$$ long "detailed" $$ long "detailed"
<=> short 'd' <=> short 'd'
<=> help "Print package modules belong to" <=> help "Print package modules belong to"
dumpSymArgSpec = CmdDumpSym <$> strArg "TMPDIR"
findArgSpec = CmdFind <$> strArg "SYMBOL" findArgSpec = CmdFind <$> strArg "SYMBOL"
docArgSpec = CmdDoc <$> strArg "MODULE" docArgSpec = CmdDoc <$> strArg "MODULE"
lintArgSpec = CmdLint lintArgSpec = CmdLint

View File

@ -8,6 +8,7 @@ import System.Directory (canonicalizePath)
import System.FilePath (pathSeparator) import System.FilePath (pathSeparator)
import Test.Hspec import Test.Hspec
import TestUtils import TestUtils
import Prelude
import Dir import Dir

View File

@ -1,7 +1,6 @@
module FindSpec where module FindSpec where
import Language.Haskell.GhcMod.Find import Language.Haskell.GhcMod.Find
import Control.Monad
import Test.Hspec import Test.Hspec
import TestUtils import TestUtils
@ -9,5 +8,5 @@ spec :: Spec
spec = do spec = do
describe "db <- loadSymbolDb" $ do describe "db <- loadSymbolDb" $ do
it "lookupSymbol' db \"head\" contains at least `Data.List'" $ do it "lookupSymbol' db \"head\" contains at least `Data.List'" $ do
db <- runD $ loadSymbolDb =<< (cradleTempDir `liftM` cradle) db <- runD $ loadSymbolDb
lookupSym "head" db `shouldContain` [ModuleString "Data.List"] lookupSym "head" db `shouldContain` [ModuleString "Data.List"]