Using PackageDescription instead of GenericPackageDescription.
This enables to pick conditional dependency in a cabal file.
This commit is contained in:
parent
f4f55d8cf0
commit
b2d2542435
@ -3,25 +3,27 @@
|
|||||||
module Language.Haskell.GhcMod.CabalApi (
|
module Language.Haskell.GhcMod.CabalApi (
|
||||||
fromCabalFile
|
fromCabalFile
|
||||||
, cabalParseFile
|
, cabalParseFile
|
||||||
, cabalBuildInfo
|
|
||||||
, cabalAllDependPackages
|
, cabalAllDependPackages
|
||||||
, cabalAllSourceDirs
|
, cabalAllSourceDirs
|
||||||
, getGHCVersion
|
, getGHCVersion
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative ((<$>))
|
||||||
import Control.Exception (throwIO)
|
import Control.Exception (throwIO)
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import Data.Maybe (maybeToList, listToMaybe)
|
import Data.Maybe (maybeToList)
|
||||||
import Data.Set (fromList, toList)
|
import Data.Set (fromList, toList)
|
||||||
import Distribution.Package (Dependency(Dependency), PackageName(PackageName))
|
import Distribution.Package (Dependency(Dependency), PackageName(PackageName))
|
||||||
import Distribution.PackageDescription
|
import Distribution.PackageDescription
|
||||||
|
import Distribution.PackageDescription.Configuration (finalizePackageDescription)
|
||||||
import Distribution.PackageDescription.Parse (readPackageDescription)
|
import Distribution.PackageDescription.Parse (readPackageDescription)
|
||||||
|
import Distribution.Simple.Compiler (CompilerId(..), CompilerFlavor(..))
|
||||||
import Distribution.Simple.Program (ghcProgram)
|
import Distribution.Simple.Program (ghcProgram)
|
||||||
import Distribution.Simple.Program.Types (programName, programFindVersion)
|
import Distribution.Simple.Program.Types (programName, programFindVersion)
|
||||||
|
import Distribution.System (buildPlatform)
|
||||||
import Distribution.Text (display)
|
import Distribution.Text (display)
|
||||||
import Distribution.Verbosity (silent)
|
import Distribution.Verbosity (silent)
|
||||||
import Distribution.Version (versionBranch)
|
import Distribution.Version (versionBranch, Version)
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
@ -32,32 +34,42 @@ fromCabalFile :: [GHCOption]
|
|||||||
-> IO ([GHCOption],[IncludeDir],[Package])
|
-> IO ([GHCOption],[IncludeDir],[Package])
|
||||||
fromCabalFile ghcOptions cradle = do
|
fromCabalFile ghcOptions cradle = do
|
||||||
cabal <- cabalParseFile cfile
|
cabal <- cabalParseFile cfile
|
||||||
case cabalBuildInfo cabal of
|
return $ cookInfo ghcOptions cradle cabal
|
||||||
Nothing -> throwIO $ userError "cabal file is broken"
|
|
||||||
Just binfo -> return $ cookInfo ghcOptions cradle cabal binfo
|
|
||||||
where
|
where
|
||||||
Just cfile = cradleCabalFile cradle
|
Just cfile = cradleCabalFile cradle
|
||||||
|
|
||||||
cookInfo :: [String] -> Cradle -> GenericPackageDescription -> BuildInfo
|
cookInfo :: [String] -> Cradle -> PackageDescription
|
||||||
-> ([GHCOption],[IncludeDir],[Package])
|
-> ([GHCOption],[IncludeDir],[Package])
|
||||||
cookInfo ghcOptions cradle cabal binfo = (gopts,idirs,depPkgs)
|
cookInfo ghcOptions cradle cabal = (gopts,idirs,depPkgs)
|
||||||
where
|
where
|
||||||
wdir = cradleCurrentDir cradle
|
wdir = cradleCurrentDir cradle
|
||||||
Just cdir = cradleCabalDir cradle
|
Just cdir = cradleCabalDir cradle
|
||||||
Just cfile = cradleCabalFile cradle
|
Just cfile = cradleCabalFile cradle
|
||||||
gopts = getGHCOptions ghcOptions binfo
|
buildInfos = cabalAllBuildInfo cabal
|
||||||
idirs = includeDirectories cdir wdir $ cabalAllSourceDirs cabal
|
gopts = getGHCOptions ghcOptions $ head buildInfos -- FIXME
|
||||||
depPkgs = removeMe cfile $ cabalAllDependPackages cabal
|
idirs = includeDirectories cdir wdir $ cabalAllSourceDirs buildInfos
|
||||||
|
depPkgs = removeMe cfile $ cabalAllDependPackages buildInfos
|
||||||
|
|
||||||
removeMe :: FilePath -> [String] -> [String]
|
removeMe :: FilePath -> [String] -> [String]
|
||||||
removeMe cabalfile = filter (/= me)
|
removeMe cabalfile = filter (/= me)
|
||||||
where
|
where
|
||||||
me = dropExtension $ takeFileName cabalfile
|
me = dropExtension $ takeFileName cabalfile
|
||||||
|
|
||||||
|
includeDirectories :: String -> String -> [FilePath] -> [String]
|
||||||
|
includeDirectories cdir wdir [] = uniqueAndSort [cdir,wdir]
|
||||||
|
includeDirectories cdir wdir dirs = uniqueAndSort (map (cdir </>) dirs ++ [cdir,wdir])
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
cabalParseFile :: FilePath -> IO GenericPackageDescription
|
cabalParseFile :: FilePath -> IO PackageDescription
|
||||||
cabalParseFile = readPackageDescription silent
|
cabalParseFile file = do
|
||||||
|
cid <- getGHCId
|
||||||
|
epgd <- readPackageDescription silent file
|
||||||
|
case toPkgDesc cid epgd of
|
||||||
|
Left _ -> throwIO $ userError "cabal file is broken"
|
||||||
|
Right (pd,_) -> return pd -- FIXME check empty
|
||||||
|
where
|
||||||
|
toPkgDesc cid = finalizePackageDescription [] (const True) buildPlatform cid []
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
@ -71,55 +83,26 @@ getGHCOptions ghcOptions binfo = ghcOptions ++ exts ++ [lang] ++ libs ++ libDirs
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
cabalBuildInfo :: GenericPackageDescription -> Maybe BuildInfo
|
cabalAllBuildInfo :: PackageDescription -> [BuildInfo]
|
||||||
cabalBuildInfo pd = fromLibrary pd <|> fromExecutable pd
|
cabalAllBuildInfo pd = libBI ++ execBI ++ testBI ++ benchBI
|
||||||
where
|
where
|
||||||
fromLibrary c = libBuildInfo . condTreeData <$> condLibrary c
|
libBI = map libBuildInfo $ maybeToList $ library pd
|
||||||
fromExecutable c = buildInfo . condTreeData . snd <$> listToMaybe (condExecutables c)
|
execBI = map buildInfo $ executables pd
|
||||||
|
testBI = map testBuildInfo $ testSuites pd
|
||||||
|
benchBI = map benchmarkBuildInfo $ benchmarks pd
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
cabalAllSourceDirs :: GenericPackageDescription -> [FilePath]
|
cabalAllSourceDirs :: [BuildInfo] -> [FilePath]
|
||||||
cabalAllSourceDirs = fromPackageDescription (f libBuildInfo) (f buildInfo) (f testBuildInfo) (f benchmarkBuildInfo)
|
cabalAllSourceDirs bis = uniqueAndSort $ concatMap hsSourceDirs bis
|
||||||
where
|
|
||||||
f getBuildInfo = concatMap (hsSourceDirs . getBuildInfo . condTreeData)
|
|
||||||
|
|
||||||
cabalAllDependPackages :: GenericPackageDescription -> [Package]
|
|
||||||
cabalAllDependPackages pd = uniqueAndSort pkgs
|
|
||||||
where
|
|
||||||
pkgs = map getDependencyPackageName $ cabalAllDependency pd
|
|
||||||
|
|
||||||
cabalAllDependency :: GenericPackageDescription -> [Dependency]
|
|
||||||
cabalAllDependency = fromPackageDescription getDeps getDeps getDeps getDeps
|
|
||||||
where
|
|
||||||
getDeps :: [Tree a] -> [Dependency]
|
|
||||||
getDeps = concatMap condTreeConstraints
|
|
||||||
|
|
||||||
getDependencyPackageName :: Dependency -> Package
|
|
||||||
getDependencyPackageName (Dependency (PackageName nm) _) = nm
|
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
type Tree = CondTree ConfVar [Dependency]
|
cabalAllDependPackages :: [BuildInfo] -> [Package]
|
||||||
|
cabalAllDependPackages bis = uniqueAndSort $ pkgs
|
||||||
fromPackageDescription :: ([Tree Library] -> [a])
|
|
||||||
-> ([Tree Executable] -> [a])
|
|
||||||
-> ([Tree TestSuite] -> [a])
|
|
||||||
-> ([Tree Benchmark] -> [a])
|
|
||||||
-> GenericPackageDescription
|
|
||||||
-> [a]
|
|
||||||
fromPackageDescription f1 f2 f3 f4 pd = lib ++ exe ++ tests ++ bench
|
|
||||||
where
|
where
|
||||||
lib = f1 . maybeToList . condLibrary $ pd
|
pkgs = map getDependencyPackageName $ concatMap targetBuildDepends bis
|
||||||
exe = f2 . map snd . condExecutables $ pd
|
getDependencyPackageName (Dependency (PackageName nm) _) = nm
|
||||||
tests = f3 . map snd . condTestSuites $ pd
|
|
||||||
bench = f4 . map snd . condBenchmarks $ pd
|
|
||||||
|
|
||||||
----------------------------------------------------------------
|
|
||||||
|
|
||||||
includeDirectories :: String -> String -> [FilePath] -> [String]
|
|
||||||
includeDirectories cdir wdir [] = uniqueAndSort [cdir,wdir]
|
|
||||||
includeDirectories cdir wdir dirs = uniqueAndSort (map (cdir </>) dirs ++ [cdir,wdir])
|
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
@ -130,14 +113,22 @@ uniqueAndSort = toList . fromList
|
|||||||
|
|
||||||
-- | Getting GHC version. 7.6.3 becames 706 in the second of the result.
|
-- | Getting GHC version. 7.6.3 becames 706 in the second of the result.
|
||||||
getGHCVersion :: IO (GHCVersion, Int)
|
getGHCVersion :: IO (GHCVersion, Int)
|
||||||
getGHCVersion = ghcVer >>= toTupple
|
getGHCVersion = toTupple <$> getGHC
|
||||||
where
|
where
|
||||||
ghcVer = programFindVersion ghcProgram silent (programName ghcProgram)
|
toTupple v
|
||||||
toTupple Nothing = throwIO $ userError "ghc not found"
|
| length vs < 2 = (verstr, 0)
|
||||||
toTupple (Just v)
|
| otherwise = (verstr, ver)
|
||||||
| length vs < 2 = return (verstr, 0)
|
|
||||||
| otherwise = return (verstr, ver)
|
|
||||||
where
|
where
|
||||||
vs = versionBranch v
|
vs = versionBranch v
|
||||||
ver = (vs !! 0) * 100 + (vs !! 1)
|
ver = (vs !! 0) * 100 + (vs !! 1)
|
||||||
verstr = intercalate "." . map show $ vs
|
verstr = intercalate "." . map show $ vs
|
||||||
|
|
||||||
|
getGHCId :: IO CompilerId
|
||||||
|
getGHCId = CompilerId GHC <$> getGHC
|
||||||
|
|
||||||
|
getGHC :: IO Version
|
||||||
|
getGHC = do
|
||||||
|
mv <- programFindVersion ghcProgram silent (programName ghcProgram)
|
||||||
|
case mv of
|
||||||
|
Nothing -> throwIO $ userError "ghc not found"
|
||||||
|
Just v -> return $ v
|
||||||
|
Loading…
Reference in New Issue
Block a user