diff --git a/Language/Haskell/GhcMod/CabalHelper.hs b/Language/Haskell/GhcMod/CabalHelper.hs index f525d40..0fa2fee 100644 --- a/Language/Haskell/GhcMod/CabalHelper.hs +++ b/Language/Haskell/GhcMod/CabalHelper.hs @@ -21,7 +21,6 @@ module Language.Haskell.GhcMod.CabalHelper , getGhcMergedPkgOptions , getCabalPackageDbStack , getStackPackageDbStack - , getCustomPkgDbStack , prepareCabalHelper ) #endif @@ -43,6 +42,7 @@ import Language.Haskell.GhcMod.Utils import Language.Haskell.GhcMod.PathsAndFiles import Language.Haskell.GhcMod.Logging import Language.Haskell.GhcMod.Output +import Language.Haskell.GhcMod.CustomPackageDb import System.FilePath import System.Directory (findExecutable) import System.Process @@ -139,18 +139,6 @@ prepareCabalHelper = do when (cradleProjectType crdl == CabalProject || cradleProjectType crdl == StackProject) $ withCabal $ liftIO $ prepare readProc projdir distdir -parseCustomPackageDb :: String -> [GhcPkgDb] -parseCustomPackageDb src = map parsePkgDb $ filter (not . null) $ lines src - where - parsePkgDb "global" = GlobalDb - parsePkgDb "user" = UserDb - parsePkgDb s = PackageDb s - -getCustomPkgDbStack :: (IOish m, GmEnv m) => m (Maybe [GhcPkgDb]) -getCustomPkgDbStack = do - mCusPkgDbFile <- liftIO . (traverse readFile <=< findCustomPackageDbFile) . cradleRootDir =<< cradle - return $ parseCustomPackageDb <$> mCusPkgDbFile - getStackPackageDbStack :: IOish m => m [GhcPkgDb] getStackPackageDbStack = do mstack <- liftIO $ findExecutable "stack" diff --git a/Language/Haskell/GhcMod/CustomPackageDb.hs b/Language/Haskell/GhcMod/CustomPackageDb.hs new file mode 100644 index 0000000..ce548eb --- /dev/null +++ b/Language/Haskell/GhcMod/CustomPackageDb.hs @@ -0,0 +1,25 @@ +module Language.Haskell.GhcMod.CustomPackageDb where + + +import Control.Applicative +import Control.Monad +import Control.Category ((.)) +import Data.Maybe +import Data.Traversable +import Language.Haskell.GhcMod.Types +import Language.Haskell.GhcMod.Monad.Types +import Language.Haskell.GhcMod.PathsAndFiles +import Prelude hiding ((.)) + + +parseCustomPackageDb :: String -> [GhcPkgDb] +parseCustomPackageDb src = map parsePkgDb $ filter (not . null) $ lines src + where + parsePkgDb "global" = GlobalDb + parsePkgDb "user" = UserDb + parsePkgDb s = PackageDb s + +getCustomPkgDbStack :: (IOish m, GmEnv m) => m (Maybe [GhcPkgDb]) +getCustomPkgDbStack = do + mCusPkgDbFile <- liftIO . (traverse readFile <=< findCustomPackageDbFile) . cradleRootDir =<< cradle + return $ parseCustomPackageDb <$> mCusPkgDbFile diff --git a/Language/Haskell/GhcMod/GhcPkg.hs b/Language/Haskell/GhcMod/GhcPkg.hs index 1d7d2d2..ef06b09 100644 --- a/Language/Haskell/GhcMod/GhcPkg.hs +++ b/Language/Haskell/GhcMod/GhcPkg.hs @@ -22,6 +22,7 @@ import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Monad.Types import Language.Haskell.GhcMod.CabalHelper import Language.Haskell.GhcMod.PathsAndFiles +import Language.Haskell.GhcMod.CustomPackageDb ghcVersion :: Int ghcVersion = read cProjectVersionInt diff --git a/Language/Haskell/GhcMod/PathsAndFiles.hs b/Language/Haskell/GhcMod/PathsAndFiles.hs index ca80bbd..47dc090 100644 --- a/Language/Haskell/GhcMod/PathsAndFiles.hs +++ b/Language/Haskell/GhcMod/PathsAndFiles.hs @@ -264,8 +264,9 @@ pkgDbStackCacheFile :: FilePath -> FilePath pkgDbStackCacheFile dist = setupConfigPath dist <.> "ghc-mod.package-db-stack" --- | @findCustomPackageDbFile dir@. Searches for a @.ghc-mod.cradle@ file in @dir@. --- If it exists in the given directory it is returned otherwise @findCradleFile@ returns @Nothing@ +-- | @findCustomPackageDbFile dir@. Searches for a @ghc-mod.package-db-stack@ file in @dir@. +-- If it exists in the given directory it is returned otherwise @findCradleFile@ +-- returns @Nothing@ findCustomPackageDbFile :: FilePath -> IO (Maybe FilePath) findCustomPackageDbFile directory = do let path = directory "ghc-mod.package-db-stack" diff --git a/Language/Haskell/GhcMod/Target.hs b/Language/Haskell/GhcMod/Target.hs index f1072ca..428b776 100644 --- a/Language/Haskell/GhcMod/Target.hs +++ b/Language/Haskell/GhcMod/Target.hs @@ -37,6 +37,7 @@ import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Utils as U import Language.Haskell.GhcMod.FileMapping import Language.Haskell.GhcMod.LightGhc +import Language.Haskell.GhcMod.CustomPackageDb import Data.Maybe import Data.Monoid as Monoid @@ -270,10 +271,11 @@ packageGhcOptions = do _ -> sandboxOpts crdl -- also works for plain projects! -sandboxOpts :: MonadIO m => Cradle -> m [String] +sandboxOpts :: (IOish m, GmEnv m) => Cradle -> m [String] sandboxOpts crdl = do + mCusPkgDb <- getCustomPkgDbStack pkgDbStack <- liftIO $ getSandboxPackageDbStack - let pkgOpts = ghcDbStackOpts pkgDbStack + let pkgOpts = ghcDbStackOpts $ fromMaybe pkgDbStack mCusPkgDb return $ ["-i" ++ d | d <- [wdir,rdir]] ++ pkgOpts ++ ["-Wall"] where (wdir, rdir) = (cradleCurrentDir crdl, cradleRootDir crdl) diff --git a/README.md b/README.md index 28b1b3e..b06463a 100644 --- a/README.md +++ b/README.md @@ -47,7 +47,7 @@ all sorts of nasty conflicts. ## Custom ghc-mod cradle -To customize the package databases used by `ghc-mod`, put a file called `ghc-mod.cradle` beside the `.cabal` file with the following syntax: +To customize the package databases used by `ghc-mod`, put a file called `ghc-mod.package-db-stack` beside the `.cabal` file with the following syntax: ``` temp directory root diff --git a/ghc-mod.cabal b/ghc-mod.cabal index a403a26..20347be 100644 --- a/ghc-mod.cabal +++ b/ghc-mod.cabal @@ -110,6 +110,7 @@ Library Language.Haskell.GhcMod.Check Language.Haskell.GhcMod.Convert Language.Haskell.GhcMod.Cradle + Language.Haskell.GhcMod.CustomPackageDb Language.Haskell.GhcMod.Debug Language.Haskell.GhcMod.Doc Language.Haskell.GhcMod.DynFlags