Use Binary for 'find' communication channel

This commit is contained in:
Nikolay Yakimov
2016-01-09 17:27:21 +03:00
parent b9c796421f
commit 68689bfcfd
6 changed files with 50 additions and 30 deletions

View File

@@ -1,4 +1,4 @@
{-# LANGUAGE CPP, BangPatterns #-}
{-# LANGUAGE CPP, DeriveGeneric #-}
module Language.Haskell.GhcMod.Find
#ifndef SPEC
@@ -31,13 +31,16 @@ import Name
import Module
import Exception
import Control.Arrow
import Control.Applicative
import Control.Monad
import Control.Monad.Trans.Control
import Control.Concurrent
import Control.DeepSeq
import Data.Function
import Data.List
import qualified Data.ByteString.Lazy as BS
import Data.Binary
import GHC.Generics (Generic)
import Data.Map (Map)
import qualified Data.Map as M
import System.Directory.ModTime
@@ -51,7 +54,10 @@ type Symbol = String
data SymbolDb = SymbolDb
{ table :: Map Symbol [ModuleString]
, timestamp :: ModTime
} deriving (Show, Read)
} deriving (Generic)
instance Binary SymbolDb
instance NFData SymbolDb
isOutdated :: IOish m => SymbolDb -> GhcModT m Bool
isOutdated db =
@@ -78,24 +84,22 @@ lookupSym sym db = M.findWithDefault [] sym $ table db
loadSymbolDb :: IOish m => GhcModT m SymbolDb
loadSymbolDb = do
ghcMod <- liftIO ghcModExecutable
readProc <- gmReadProcess
(!db, !ts) <- first M.fromAscList . read <$> liftIO
(readProc ghcMod ["--verbose", "error", "dumpsym"] "")
return SymbolDb {
table = db
, timestamp = ts
}
readProc <- gmReadProcess'
out <- liftIO $ readProc ghcMod ["--verbose", "error", "dumpsym"] ""
return $!! decode out
----------------------------------------------------------------
-- used 'ghc-mod dumpsym'
-- | Dumps a tuple of
-- (\[('Symbol',\['ModuleString'\])\], 'ModTime') to stdout
dumpSymbol :: IOish m => GhcModT m String
-- | Dumps a 'Binary' representation of 'SymbolDb' to stdout
dumpSymbol :: IOish m => GhcModT m ()
dumpSymbol = do
timestamp <- liftIO getCurrentModTime
ts <- liftIO getCurrentModTime
st <- runGmPkgGhc getGlobalSymbolTable
return . show $ (st, timestamp)
liftIO . BS.putStr $ encode SymbolDb {
table = M.fromAscList st
, timestamp = ts
}
-- | Check whether given file is older than any file from the given set.
-- Returns True if given file does not exist.

View File

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

View File

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