2014-05-18 23:20:58 +00:00
|
|
|
{-# LANGUAGE BangPatterns, ScopedTypeVariables, TupleSections #-}
|
2014-04-15 03:13:10 +00:00
|
|
|
module Language.Haskell.GhcMod.GhcPkg (
|
2014-05-08 03:42:45 +00:00
|
|
|
ghcPkgDbOpt
|
2014-04-15 03:13:10 +00:00
|
|
|
, ghcPkgDbStackOpts
|
|
|
|
, ghcDbStackOpts
|
|
|
|
, ghcDbOpt
|
2014-04-30 23:48:49 +00:00
|
|
|
, fromInstalledPackageId
|
2014-05-03 12:51:58 +00:00
|
|
|
, fromInstalledPackageId'
|
2014-04-15 03:13:10 +00:00
|
|
|
, getSandboxDb
|
|
|
|
, getPackageDbStack
|
2014-09-23 04:47:32 +00:00
|
|
|
, getPackageCachePath
|
|
|
|
, packageCache
|
|
|
|
, packageConfDir
|
2014-04-15 03:13:10 +00:00
|
|
|
) where
|
|
|
|
|
2014-09-23 04:47:32 +00:00
|
|
|
import Config (cProjectVersion, cTargetPlatformString, cProjectVersionInt)
|
2014-05-08 03:42:45 +00:00
|
|
|
import Control.Applicative ((<$>))
|
2014-05-18 23:20:58 +00:00
|
|
|
import Control.Exception (SomeException(..))
|
2014-05-09 19:12:52 +00:00
|
|
|
import qualified Control.Exception as E
|
2014-05-08 03:42:45 +00:00
|
|
|
import Data.Char (isSpace)
|
2014-04-17 21:40:11 +00:00
|
|
|
import Data.List (isPrefixOf, intercalate)
|
2014-04-30 23:48:49 +00:00
|
|
|
import Data.List.Split (splitOn)
|
|
|
|
import Distribution.Package (InstalledPackageId(..))
|
2014-09-23 04:47:32 +00:00
|
|
|
import Exception (handleIO)
|
2014-04-16 02:50:31 +00:00
|
|
|
import Language.Haskell.GhcMod.Types
|
2014-04-19 06:20:16 +00:00
|
|
|
import Language.Haskell.GhcMod.Utils
|
2014-09-23 04:47:32 +00:00
|
|
|
import System.Directory (doesDirectoryExist, getAppUserDataDirectory)
|
2014-04-16 02:32:36 +00:00
|
|
|
import System.FilePath ((</>))
|
2014-04-15 03:13:10 +00:00
|
|
|
|
2014-04-15 15:14:10 +00:00
|
|
|
ghcVersion :: Int
|
|
|
|
ghcVersion = read cProjectVersionInt
|
|
|
|
|
2014-04-15 03:13:10 +00:00
|
|
|
-- | Get path to sandbox package db
|
|
|
|
getSandboxDb :: FilePath -- ^ Path to the cabal package root directory
|
|
|
|
-- (containing the @cabal.sandbox.config@ file)
|
|
|
|
-> IO FilePath
|
2014-04-16 02:50:31 +00:00
|
|
|
getSandboxDb cdir = getSandboxDbDir (cdir </> "cabal.sandbox.config")
|
2014-04-15 03:13:10 +00:00
|
|
|
|
|
|
|
-- | Extract the sandbox package db directory from the cabal.sandbox.config file.
|
|
|
|
-- Exception is thrown if the sandbox config file is broken.
|
|
|
|
getSandboxDbDir :: FilePath -- ^ Path to the @cabal.sandbox.config@ file
|
|
|
|
-> IO FilePath
|
|
|
|
getSandboxDbDir sconf = do
|
|
|
|
-- Be strict to ensure that an error can be caught.
|
|
|
|
!path <- extractValue . parse <$> readFile sconf
|
|
|
|
return path
|
|
|
|
where
|
|
|
|
key = "package-db:"
|
|
|
|
keyLen = length key
|
|
|
|
|
|
|
|
parse = head . filter (key `isPrefixOf`) . lines
|
|
|
|
extractValue = dropWhileEnd isSpace . dropWhile isSpace . drop keyLen
|
|
|
|
|
2014-09-23 04:47:32 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-15 03:13:10 +00:00
|
|
|
getPackageDbStack :: FilePath -- ^ Project Directory (where the
|
|
|
|
-- cabal.sandbox.config file would be if it
|
|
|
|
-- exists)
|
|
|
|
-> IO [GhcPkgDb]
|
2014-05-09 18:38:35 +00:00
|
|
|
getPackageDbStack cdir =
|
2014-04-15 03:13:10 +00:00
|
|
|
(getSandboxDb cdir >>= \db -> return [GlobalDb, PackageDb db])
|
2014-05-18 23:20:58 +00:00
|
|
|
`E.catch` \(_ :: SomeException) -> return [GlobalDb, UserDb]
|
2014-04-15 03:13:10 +00:00
|
|
|
|
2014-09-23 04:47:32 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-05-03 12:51:58 +00:00
|
|
|
fromInstalledPackageId' :: InstalledPackageId -> Maybe Package
|
|
|
|
fromInstalledPackageId' pid = let
|
2014-04-30 23:48:49 +00:00
|
|
|
InstalledPackageId pkg = pid
|
|
|
|
in case reverse $ splitOn "-" pkg of
|
|
|
|
i:v:rest -> Just (intercalate "-" (reverse rest), v, i)
|
|
|
|
_ -> Nothing
|
|
|
|
|
2014-05-03 12:51:58 +00:00
|
|
|
fromInstalledPackageId :: InstalledPackageId -> Package
|
|
|
|
fromInstalledPackageId pid =
|
|
|
|
case fromInstalledPackageId' pid of
|
|
|
|
Just p -> p
|
|
|
|
Nothing -> error $
|
|
|
|
"fromInstalledPackageId: `"++show pid++"' is not a valid package-id"
|
|
|
|
|
2014-09-23 04:47:32 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-15 03:13:10 +00:00
|
|
|
-- | Get options needed to add a list of package dbs to ghc-pkg's db stack
|
|
|
|
ghcPkgDbStackOpts :: [GhcPkgDb] -- ^ Package db stack
|
|
|
|
-> [String]
|
2014-04-16 02:52:49 +00:00
|
|
|
ghcPkgDbStackOpts dbs = ghcPkgDbOpt `concatMap` dbs
|
2014-04-15 03:13:10 +00:00
|
|
|
|
|
|
|
-- | Get options needed to add a list of package dbs to ghc's db stack
|
|
|
|
ghcDbStackOpts :: [GhcPkgDb] -- ^ Package db stack
|
2014-04-16 02:50:31 +00:00
|
|
|
-> [String]
|
2014-04-16 02:52:49 +00:00
|
|
|
ghcDbStackOpts dbs = ghcDbOpt `concatMap` dbs
|
2014-04-15 03:13:10 +00:00
|
|
|
|
2014-09-23 04:47:32 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-15 03:13:10 +00:00
|
|
|
ghcPkgDbOpt :: GhcPkgDb -> [String]
|
|
|
|
ghcPkgDbOpt GlobalDb = ["--global"]
|
|
|
|
ghcPkgDbOpt UserDb = ["--user"]
|
2014-04-15 15:14:10 +00:00
|
|
|
ghcPkgDbOpt (PackageDb pkgDb)
|
2014-04-16 02:50:31 +00:00
|
|
|
| ghcVersion < 706 = ["--no-user-package-conf", "--package-conf=" ++ pkgDb]
|
|
|
|
| otherwise = ["--no-user-package-db", "--package-db=" ++ pkgDb]
|
2014-04-15 03:13:10 +00:00
|
|
|
|
|
|
|
ghcDbOpt :: GhcPkgDb -> [String]
|
2014-04-16 02:50:31 +00:00
|
|
|
ghcDbOpt GlobalDb
|
|
|
|
| ghcVersion < 706 = ["-global-package-conf"]
|
|
|
|
| otherwise = ["-global-package-db"]
|
|
|
|
ghcDbOpt UserDb
|
|
|
|
| ghcVersion < 706 = ["-user-package-conf"]
|
|
|
|
| otherwise = ["-user-package-db"]
|
2014-04-15 15:14:10 +00:00
|
|
|
ghcDbOpt (PackageDb pkgDb)
|
2014-04-16 02:50:31 +00:00
|
|
|
| ghcVersion < 706 = ["-no-user-package-conf", "-package-conf", pkgDb]
|
|
|
|
| otherwise = ["-no-user-package-db", "-package-db", pkgDb]
|
2014-09-23 04:47:32 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
|
|
|
packageCache :: String
|
|
|
|
packageCache = "package.cache"
|
|
|
|
|
|
|
|
packageConfDir :: String
|
|
|
|
packageConfDir = "package.conf.d"
|
|
|
|
|
|
|
|
-- fixme: error handling
|
2014-09-23 12:28:03 +00:00
|
|
|
getPackageCachePath :: Cradle -> IO FilePath
|
|
|
|
getPackageCachePath crdl = do
|
2014-09-23 04:47:32 +00:00
|
|
|
let u:_ = filter (/= GlobalDb) $ cradlePkgDbStack crdl
|
2014-09-23 12:28:03 +00:00
|
|
|
Just db <- resolvePath u
|
2014-09-23 04:47:32 +00:00
|
|
|
return db
|
|
|
|
|
|
|
|
--- Copied from ghc module `Packages' unfortunately it's not exported :/
|
2014-09-23 12:28:03 +00:00
|
|
|
resolvePath :: GhcPkgDb -> IO (Maybe FilePath)
|
|
|
|
resolvePath (PackageDb name) = return $ Just name
|
|
|
|
resolvePath UserDb = handleIO (\_ -> return Nothing) $ do
|
2014-09-23 04:47:32 +00:00
|
|
|
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
|
2014-09-23 12:28:03 +00:00
|
|
|
resolvePath _ = error "GlobalDb cannot be used in resolvePath"
|