Merge branch 'master' (early part) into release

Conflicts:
	Language/Haskell/GhcMod/Utils.hs
This commit is contained in:
Daniel Gröber
2014-10-30 01:12:28 +01:00
10 changed files with 109 additions and 88 deletions

View File

@@ -2,6 +2,7 @@ module Language.Haskell.GhcMod.Cradle (
findCradle
, findCradle'
, findCradleWithoutSandbox
, cleanupCradle
) where
import Language.Haskell.GhcMod.Types
@@ -12,8 +13,10 @@ import qualified Control.Exception as E
import Control.Exception.IOChoice ((||>))
import Control.Monad (filterM)
import Data.List (isSuffixOf)
import System.Directory (getCurrentDirectory, getDirectoryContents, doesFileExist)
import System.Directory (getCurrentDirectory, getDirectoryContents, doesFileExist, getTemporaryDirectory, removeDirectoryRecursive)
import System.FilePath ((</>), takeDirectory)
import System.IO.Temp
----------------------------------------------------------------
@@ -27,13 +30,26 @@ findCradle = findCradle' =<< getCurrentDirectory
findCradle' :: FilePath -> IO Cradle
findCradle' dir = cabalCradle dir ||> sandboxCradle dir ||> plainCradle dir
newTempDir :: FilePath -> IO FilePath
newTempDir dir =
flip createTempDirectory uniqPathName =<< getTemporaryDirectory
where
uniqPathName = "ghc-mod" ++ map escapeSlash dir
escapeSlash '/' = '-'
escapeSlash c = c
cleanupCradle :: Cradle -> IO ()
cleanupCradle crdl = removeDirectoryRecursive $ cradleTempDir crdl
cabalCradle :: FilePath -> IO Cradle
cabalCradle wdir = do
(rdir,cfile) <- cabalDir wdir
pkgDbStack <- getPackageDbStack rdir
tmpDir <- newTempDir rdir
return Cradle {
cradleCurrentDir = wdir
, cradleRootDir = rdir
, cradleTempDir = tmpDir
, cradleCabalFile = Just cfile
, cradlePkgDbStack = pkgDbStack
}
@@ -42,17 +58,22 @@ sandboxCradle :: FilePath -> IO Cradle
sandboxCradle wdir = do
rdir <- getSandboxDir wdir
pkgDbStack <- getPackageDbStack rdir
tmpDir <- newTempDir rdir
return Cradle {
cradleCurrentDir = wdir
, cradleRootDir = rdir
, cradleTempDir = tmpDir
, cradleCabalFile = Nothing
, cradlePkgDbStack = pkgDbStack
}
plainCradle :: FilePath -> IO Cradle
plainCradle wdir = return Cradle {
plainCradle wdir = do
tmpDir <- newTempDir wdir
return Cradle {
cradleCurrentDir = wdir
, cradleRootDir = wdir
, cradleTempDir = tmpDir
, cradleCabalFile = Nothing
, cradlePkgDbStack = [GlobalDb, UserDb]
}

View File

@@ -17,7 +17,6 @@ module Language.Haskell.GhcMod.Find
import Control.Applicative ((<$>))
import Control.Monad (when, void)
import Control.Monad.Error.Class
import Data.Function (on)
import Data.List (groupBy, sort)
import Data.Maybe (fromMaybe)
@@ -87,10 +86,11 @@ lookupSym sym db = fromMaybe [] $ M.lookup sym $ table db
---------------------------------------------------------------
-- | Loading a file and creates 'SymbolDb'.
loadSymbolDb :: (IOish m, MonadError GhcModError m) => m SymbolDb
loadSymbolDb :: IOish m => GhcModT m SymbolDb
loadSymbolDb = do
ghcMod <- liftIO ghcModExecutable
file <- chop <$> readProcess' ghcMod ["dumpsym"]
tmpdir <- liftIO . getPackageCachePath =<< cradle
file <- chop <$> readProcess' ghcMod ["dumpsym", tmpdir]
!db <- M.fromAscList . map conv . lines <$> liftIO (readFile file)
return $ SymbolDb {
table = db
@@ -110,10 +110,8 @@ loadSymbolDb = do
-- if the file does not exist or is invalid.
-- The file name is printed.
dumpSymbol :: IOish m => GhcModT m String
dumpSymbol = do
crdl <- cradle
dir <- liftIO $ getPackageCachePath crdl
dumpSymbol :: IOish m => FilePath -> GhcModT m String
dumpSymbol dir = do
let cache = dir </> symbolCache
pkgdb = dir </> packageCache

View File

@@ -16,16 +16,19 @@ module Language.Haskell.GhcMod.GhcPkg (
import Config (cProjectVersion, cTargetPlatformString, cProjectVersionInt)
import Control.Applicative ((<$>))
import Control.Exception (SomeException(..))
import Control.Monad
import qualified Control.Exception as E
import Data.Char (isSpace)
import Data.List (isPrefixOf, intercalate)
import Data.List.Split (splitOn)
import Data.Maybe
import Distribution.Package (InstalledPackageId(..))
import Exception (handleIO)
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Utils
import System.Directory (doesDirectoryExist, getAppUserDataDirectory)
import System.FilePath ((</>))
import qualified Data.Traversable as T
ghcVersion :: Int
ghcVersion = read cProjectVersionInt
@@ -117,12 +120,14 @@ packageCache = "package.cache"
packageConfDir :: String
packageConfDir = "package.conf.d"
-- fixme: error handling
getPackageCachePath :: Cradle -> IO FilePath
getPackageCachePath crdl = do
let u:_ = filter (/= GlobalDb) $ cradlePkgDbStack crdl
Just db <- resolvePath u
return db
let mu = listToMaybe $ filter (/= GlobalDb) $ cradlePkgDbStack crdl
mdb <- join <$> resolvePath `T.traverse` mu
let dir = case mdb of
Just db -> db
Nothing -> cradleTempDir crdl
return dir
--- Copied from ghc module `Packages' unfortunately it's not exported :/
resolvePath :: GhcPkgDb -> IO (Maybe FilePath)

View File

@@ -244,6 +244,9 @@ newGhcModEnv opt dir = do
, gmCradle = c
}
cleanupGhcModEnv :: GhcModEnv -> IO ()
cleanupGhcModEnv env = cleanupCradle $ gmCradle env
-- | Run a @GhcModT m@ computation.
runGhcModT :: IOish m
=> Options
@@ -251,11 +254,13 @@ runGhcModT :: IOish m
-> m (Either GhcModError a, GhcModLog)
runGhcModT opt action = do
env <- liftBase $ newGhcModEnv opt =<< getCurrentDirectory
first (fst <$>) <$> (runGhcModT' env defaultState $ do
r <- first (fst <$>) <$> (runGhcModT' env defaultState $ do
dflags <- getSessionDynFlags
defaultCleanupHandler dflags $ do
initializeFlagsWithCradle opt (gmCradle env)
action)
liftBase $ cleanupGhcModEnv env
return r
-- | @hoistGhcModT result@. Embed a GhcModT computation's result into a GhcModT
-- computation. Note that if the computation that returned @result@ modified the

View File

@@ -19,9 +19,10 @@ type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
-- | Output style.
data OutputStyle = LispStyle -- ^ S expression style.
| PlainStyle -- ^ Plain textstyle.
deriving (Show)
-- | The type for line separator. Historically, a Null string is used.
newtype LineSeparator = LineSeparator String
newtype LineSeparator = LineSeparator String deriving (Show)
data Options = Options {
outputStyle :: OutputStyle
@@ -40,7 +41,7 @@ data Options = Options {
-- | If 'True', 'browse' will return fully qualified name
, qualified :: Bool
, hlintOpts :: [String]
}
} deriving (Show)
-- | A default 'Options'.
@@ -65,6 +66,8 @@ data Cradle = Cradle {
cradleCurrentDir :: FilePath
-- | The project root directory.
, cradleRootDir :: FilePath
-- | Per-Project temporary directory
, cradleTempDir :: FilePath
-- | The file name of the found cabal file.
, cradleCabalFile :: Maybe FilePath
-- | Package database stack

View File

@@ -1,16 +1,15 @@
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.Utils where
import Control.Applicative ((<$>))
import Language.Haskell.GhcMod.Error
import MonadUtils (MonadIO, liftIO)
import System.Directory (getCurrentDirectory, setCurrentDirectory)
import System.Exit (ExitCode(..))
import System.Process (readProcessWithExitCode)
import System.FilePath (takeDirectory)
import System.Environment
#ifndef SPEC
import System.FilePath ((</>))
import Control.Applicative ((<$>))
import System.Environment
import System.FilePath ((</>),takeDirectory)
#endif
-- dropWhileEnd is not provided prior to base 4.5.0.0.
@@ -56,11 +55,6 @@ ghcModExecutable :: IO FilePath
ghcModExecutable = do
dir <- getExecutablePath'
return $ dir </> "ghc-mod"
#else
ghcModExecutable = do _ <- getExecutablePath' -- get rid of unused warning when
-- compiling spec
return "dist/build/ghc-mod/ghc-mod"
#endif
where
getExecutablePath' :: IO FilePath
# if __GLASGOW_HASKELL__ >= 706
@@ -68,3 +62,6 @@ ghcModExecutable = do _ <- getExecutablePath' -- get rid of unused warning when
# else
getExecutablePath' = return ""
# endif
#else
ghcModExecutable = return "dist/build/ghc-mod/ghc-mod"
#endif