From f38daf67730fe31b865528eb972c619857e62a5c Mon Sep 17 00:00:00 2001 From: alexwl Date: Mon, 8 Oct 2018 02:40:18 +0300 Subject: Update cabal-helper to version 0.8.1.2 that supports Cabal (>=1.14 && <1.26 || >=2.0 && <2.5) Building cabal-helper-0.8.1.2 with Stack failed with 'Dependency cycle detected' error. It seems to be https://github.com/commercialhaskell/stack/issues/4265 Stack bug. As a temporary solution I added source code of cabal-helper package to vendor directory and commented out 'build-tool-depends: cabal-helper:cabal-helper-wrapper' line in the cabal-helper.cabal file. --- .../CabalHelper/Compiletime/Compat/Environment.hs | 35 + .../CabalHelper/Compiletime/Compat/ProgramDb.hs | 30 + .../src/CabalHelper/Compiletime/Compat/Version.hs | 49 ++ .../src/CabalHelper/Compiletime/Compile.hs | 736 ++++++++++++++++++ .../src/CabalHelper/Compiletime/Data.hs | 81 ++ .../src/CabalHelper/Compiletime/Log.hs | 45 ++ .../src/CabalHelper/Compiletime/Types.hs | 42 + .../src/CabalHelper/Compiletime/Wrapper.hs | 227 ++++++ .../src/CabalHelper/Runtime/Main.hs | 841 +++++++++++++++++++++ .../src/CabalHelper/Shared/Common.hs | 150 ++++ .../src/CabalHelper/Shared/InterfaceTypes.hs | 81 ++ .../src/CabalHelper/Shared/Sandbox.hs | 78 ++ 12 files changed, 2395 insertions(+) create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Environment.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/ProgramDb.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Version.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compile.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Data.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Log.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Types.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Wrapper.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Runtime/Main.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Common.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/InterfaceTypes.hs create mode 100644 vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Sandbox.hs (limited to 'vendor/cabal-helper-0.8.1.2/src/CabalHelper') diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Environment.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Environment.hs new file mode 100644 index 0000000..58bb9ee --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Environment.hs @@ -0,0 +1,35 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2017 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP #-} +module CabalHelper.Compiletime.Compat.Environment where + +import qualified System.Environment +#ifndef mingw32_HOST_OS +import qualified System.Posix.Env (setEnv) +#endif + +lookupEnv :: String -> IO (Maybe String) +lookupEnv var = + do env <- System.Environment.getEnvironment + return (lookup var env) + +setEnv :: String -> String -> IO () +#ifdef mingw32_HOST_OS +setEnv = System.Environment.setEnv +#else +setEnv k v = System.Posix.Env.setEnv k v True +#endif diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/ProgramDb.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/ProgramDb.hs new file mode 100644 index 0000000..56b033c --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/ProgramDb.hs @@ -0,0 +1,30 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP #-} +module CabalHelper.Compiletime.Compat.ProgramDb + ( defaultProgramDb + , programPath + , lookupProgram + , ghcProgram + , ghcPkgProgram + ) where + +import Distribution.Simple.Program + +#if !MIN_VERSION_Cabal(2,0,0) +defaultProgramDb = defaultProgramConfiguration +#endif diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Version.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Version.hs new file mode 100644 index 0000000..5d4f5f5 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compat/Version.hs @@ -0,0 +1,49 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2017-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP #-} +module CabalHelper.Compiletime.Compat.Version + ( DataVersion + , toDataVersion + , fromDataVersion + , Data.Version.showVersion + , makeDataVersion + ) where + +import qualified Data.Version +import qualified Distribution.Version (Version) +#if MIN_VERSION_Cabal(2,0,0) +import qualified Distribution.Version (versionNumbers, mkVersion) +#endif + +type DataVersion = Data.Version.Version + +toDataVersion :: Distribution.Version.Version -> Data.Version.Version +fromDataVersion :: Data.Version.Version -> Distribution.Version.Version +#if MIN_VERSION_Cabal(2,0,0) +toDataVersion v = Data.Version.Version (Distribution.Version.versionNumbers v) [] +fromDataVersion (Data.Version.Version vs _) = Distribution.Version.mkVersion vs +#else +toDataVersion = id +fromDataVersion = id +#endif + +makeDataVersion :: [Int] -> Data.Version.Version +#if MIN_VERSION_base(4,8,0) +makeDataVersion = Data.Version.makeVersion +#else +makeDataVersion xs = Data.Version.Version xs [] +#endif diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compile.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compile.hs new file mode 100644 index 0000000..8da426f --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Compile.hs @@ -0,0 +1,736 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +{-# LANGUAGE RecordWildCards, FlexibleContexts, NamedFieldPuns, DeriveFunctor, +GADTs #-} + +{-| +Module : CabalHelper.Compiletime.Compile +Description : Runtime compilation machinery +License : GPL-3 +-} + +module CabalHelper.Compiletime.Compile where + +import Cabal.Plan +import Control.Applicative +import Control.Arrow +import Control.Exception as E +import Control.Monad +import Control.Monad.Trans.Maybe +import Control.Monad.IO.Class +import Data.Char +import Data.List +import Data.Maybe +import Data.String +import Data.Version +import GHC.IO.Exception (IOErrorType(OtherError)) +import Text.Printf +import Text.Read +import System.Directory +import System.FilePath +import System.Process +import System.Exit +import System.Environment +import System.IO +import System.IO.Error +import System.IO.Temp +import Prelude + + +import qualified Data.Text as Text +import qualified Data.Map.Strict as Map + +import Distribution.System (buildPlatform) +import Distribution.Text (display) + +import Paths_cabal_helper (version) +import CabalHelper.Compiletime.Data +import CabalHelper.Compiletime.Log +import CabalHelper.Compiletime.Types +import CabalHelper.Shared.Common +import CabalHelper.Shared.Sandbox (getSandboxPkgDb) + +data Compile + = CompileWithCabalSource + { compCabalSourceDir :: CabalSourceDir + , compCabalSourceVersion :: Version + } + | CompileWithCabalPackage + { compPackageDb :: Maybe PackageDbDir + , compCabalVersion :: CabalVersion + , compPackageDeps :: [String] + , compProductTarget :: CompilationProductScope + } + +data CompPaths = CompPaths + { compSrcDir :: FilePath + , compOutDir :: FilePath + , compExePath :: FilePath + } + +-- | The Helper executable we produce as a compilation product can either be +-- placed in a per-project location, or a per-user/global location in the user's +-- home directory. This type controls where the compilation process places the +-- executable. +data CompilationProductScope = CPSGlobal | CPSProject + +compileHelper :: Options -> Version -> FilePath -> Maybe (PlanJson, FilePath) -> FilePath -> IO (Either ExitCode FilePath) +compileHelper opts hdrCabalVersion projdir mnewstyle distdir = do + ghcVer <- ghcVersion opts + Just (prepare, comp) <- runMaybeT $ msum $ + case oCabalPkgDb opts of + Nothing -> + [ compileCabalSource + , compileNewBuild ghcVer + , compileSandbox ghcVer + , compileGlobal + , MaybeT $ Just <$> compileWithCabalInPrivatePkgDb + ] + Just db -> + [ return $ (return (), compileWithPkg (Just db) hdrCabalVersion CPSProject) + ] + + appdir <- appCacheDir + + let cp@CompPaths {compExePath} = compPaths appdir distdir comp + exists <- doesFileExist compExePath + if exists + then do + vLog opts $ "helper already compiled, using exe: "++compExePath + return (Right compExePath) + else do + vLog opts $ "helper exe does not exist, compiling "++compExePath + prepare >> compile comp cp opts + + where + logMsg = "using helper compiled with Cabal from " + +-- for relaxed deps: find (sameMajorVersionAs hdrCabalVersion) . reverse . sort + + -- | Check if this version is globally available + compileGlobal :: MaybeT IO (IO (), Compile) + compileGlobal = do + cabal_versions <- listCabalVersions opts + ver <- MaybeT $ return $ find (== hdrCabalVersion) cabal_versions + vLog opts $ logMsg ++ "user/global package-db" + return $ (return (), compileWithPkg Nothing ver CPSGlobal) + + -- | Check if this version is available in the project sandbox + compileSandbox :: Version -> MaybeT IO (IO (), Compile) + compileSandbox ghcVer = do + let mdb_path = getSandboxPkgDb projdir (display buildPlatform) ghcVer + sandbox <- PackageDbDir <$> MaybeT mdb_path + cabal_versions <- listCabalVersions' opts (Just sandbox) + ver <- MaybeT $ return $ find (== hdrCabalVersion) cabal_versions + vLog opts $ logMsg ++ "sandbox package-db" + return $ (return (), compileWithPkg (Just sandbox) ver CPSProject) + + compileNewBuild :: Version -> MaybeT IO (IO (), Compile) + compileNewBuild ghcVer = do + (PlanJson {pjUnits}, distdir_newstyle) <- maybe mzero pure mnewstyle + let cabal_pkgid = + PkgId (PkgName (Text.pack "Cabal")) + (Ver $ versionBranch hdrCabalVersion) + mcabal_unit = listToMaybe $ + Map.elems $ Map.filter (\Unit {..} -> uPId == cabal_pkgid) pjUnits + Unit {} <- maybe mzero pure mcabal_unit + let inplace_db_path = distdir_newstyle + "packagedb" ("ghc-" ++ showVersion ghcVer) + inplace_db = PackageDbDir inplace_db_path + cabal_versions <- listCabalVersions' opts (Just inplace_db) + ver <- MaybeT $ return $ find (== hdrCabalVersion) cabal_versions + vLog opts $ logMsg ++ "v2-build package-db " ++ inplace_db_path + return $ (return (), compileWithPkg (Just inplace_db) ver CPSProject) + + -- | Compile the requested Cabal version into an isolated package-db if it's + -- not there already + compileWithCabalInPrivatePkgDb :: IO (IO (), Compile) + compileWithCabalInPrivatePkgDb = do + db@(PackageDbDir db_path) + <- getPrivateCabalPkgDb opts (CabalVersion hdrCabalVersion) + vLog opts $ logMsg ++ "private package-db in " ++ db_path + return (prepare db, compileWithPkg (Just db) hdrCabalVersion CPSGlobal) + where + prepare db = do + db_exists <- liftIO $ cabalVersionExistsInPkgDb opts hdrCabalVersion db + when (not db_exists) $ + void $ installCabal opts (Right hdrCabalVersion) `E.catch` + \(SomeException _) -> errorInstallCabal hdrCabalVersion distdir + + -- | See if we're in a cabal source tree + compileCabalSource :: MaybeT IO (IO (), Compile) + compileCabalSource = do + let cabalFile = projdir "Cabal.cabal" + cabalSrc <- liftIO $ doesFileExist cabalFile + let projdir' = CabalSourceDir projdir + case cabalSrc of + False -> mzero + True -> do + vLog opts $ "projdir looks like Cabal source tree (Cabal.cabal exists)" + cf <- liftIO $ readFile cabalFile + let buildType = cabalFileBuildType cf + ver = cabalFileVersion cf + + case buildType of + "simple" -> do + vLog opts $ "Cabal source tree is build-type:simple, moving on" + mzero + "custom" -> do + vLog opts $ "compiling helper with local Cabal source tree" + return $ (return (), compileWithCabalSource projdir' ver) + _ -> error $ "compileCabalSource: unknown build-type: '"++buildType++"'" + + compileWithCabalSource srcDir ver = + CompileWithCabalSource + { compCabalSourceDir = srcDir + , compCabalSourceVersion = ver + } + + compileWithPkg mdb ver target = + CompileWithCabalPackage + { compPackageDb = mdb + , compCabalVersion = CabalVersion ver + , compPackageDeps = [cabalPkgId ver] + , compProductTarget = target + } + + cabalPkgId v = "Cabal-" ++ showVersion v + +compile :: Compile -> CompPaths -> Options -> IO (Either ExitCode FilePath) +compile comp paths@CompPaths {..} opts@Options {..} = do + createDirectoryIfMissing True compOutDir + createHelperSources compSrcDir + + vLog opts $ "compSrcDir: " ++ compSrcDir + vLog opts $ "compOutDir: " ++ compOutDir + vLog opts $ "compExePath: " ++ compExePath + + invokeGhc opts $ compGhcInvocation comp paths + +compPaths :: FilePath -> FilePath -> Compile -> CompPaths +compPaths appdir distdir c = + case c of + CompileWithCabalPackage {compProductTarget=CPSGlobal,..} -> CompPaths {..} + where + compSrcDir = appdir exeName compCabalVersion <.> "build" + compOutDir = compSrcDir + compExePath = appdir exeName compCabalVersion + + CompileWithCabalPackage {compProductTarget=CPSProject,..} -> distdirPaths + CompileWithCabalSource {..} -> distdirPaths + where + distdirPaths = CompPaths {..} + where + compSrcDir = distdir "cabal-helper" + compOutDir = compSrcDir + compExePath = compOutDir "cabal-helper" + +data GhcInvocation = GhcInvocation + { giOutDir :: FilePath + , giOutput :: FilePath + , giCPPOptions :: [String] + , giPackageDBs :: [PackageDbDir] + , giIncludeDirs :: [FilePath] + , giHideAllPackages :: Bool + , giPackages :: [String] + , giWarningFlags :: [String] + , giInputs :: [String] + } + +compGhcInvocation :: Compile -> CompPaths -> GhcInvocation +compGhcInvocation comp CompPaths {..} = + case comp of + CompileWithCabalSource {..} -> + GhcInvocation + { giIncludeDirs = [compSrcDir, unCabalSourceDir compCabalSourceDir] + , giPackageDBs = [] + , giHideAllPackages = False + , giPackages = [] + , giCPPOptions = cppOptions compCabalSourceVersion + ++ [cabalVersionMacro compCabalSourceVersion] + , .. + } + CompileWithCabalPackage {..} -> + GhcInvocation + { giIncludeDirs = [compSrcDir] + , giPackageDBs = maybeToList compPackageDb + , giHideAllPackages = True + , giPackages = + [ "base" + , "containers" + , "directory" + , "filepath" + , "process" + , "bytestring" + , "ghc-prim" + ] ++ compPackageDeps + , giCPPOptions = cppOptions (unCabalVersion compCabalVersion) + , .. + } + where + + unCabalVersion (CabalVersion ver) = ver + unCabalVersion (CabalHEAD _) = Version [10000000, 0, 0] [] + + cppOptions cabalVer = + [ "-DCABAL_HELPER=1" + , cabalMinVersionMacro cabalVer + ] + + giOutDir = compOutDir + giOutput = compExePath + giWarningFlags = [ "-w" ] -- no point in bothering end users with warnings + giInputs = [compSrcDir"CabalHelper""Runtime""Main.hs"] + +cabalVersionMacro :: Version -> String +cabalVersionMacro (Version vs _) = + "-DCABAL_VERSION="++intercalate "," (map show vs) + +cabalMinVersionMacro :: Version -> String +cabalMinVersionMacro (Version (mj1:mj2:mi:_) _) = + "-DCH_MIN_VERSION_Cabal(major1,major2,minor)=\ + \( (major1) < "++show mj1++" \ + \|| (major1) == "++show mj1++" && (major2) < "++show mj2++" \ + \|| (major1) == "++show mj1++" && (major2) == "++show mj2++" && (minor) <= "++show mi++ + ")" +cabalMinVersionMacro _ = + error "cabalMinVersionMacro: Version must have at least 3 components" + +invokeGhc :: Options -> GhcInvocation -> IO (Either ExitCode FilePath) +invokeGhc opts@Options {..} GhcInvocation {..} = do + rv <- callProcessStderr' opts Nothing oGhcProgram $ concat + [ [ "-outputdir", giOutDir + , "-o", giOutput + ] + , map ("-optP"++) giCPPOptions + , map ("-package-conf="++) $ unPackageDbDir <$> giPackageDBs + , map ("-i"++) $ nub $ "" : giIncludeDirs + , if giHideAllPackages then ["-hide-all-packages"] else [] + , concatMap (\p -> ["-package", p]) giPackages + , giWarningFlags + , ["--make"] + , giInputs + ] + return $ + case rv of + ExitSuccess -> Right giOutput + e@(ExitFailure _) -> Left e + + +-- | Cabal library version we're compiling the helper exe against. +data CabalVersion + = CabalHEAD { cvCommitId :: CommitId } + | CabalVersion { cabalVersion :: Version } + +newtype CommitId = CommitId { unCommitId :: String } + +exeName :: CabalVersion -> String +exeName (CabalHEAD commitid) = intercalate "-" + [ "cabal-helper" ++ showVersion version + , "CabalHEAD" ++ unCommitId commitid + ] +exeName CabalVersion {cabalVersion} = intercalate "-" + [ "cabal-helper" ++ showVersion version + , "Cabal" ++ showVersion cabalVersion + ] + +readProcess' :: Options -> FilePath -> [String] -> String -> IO String +readProcess' opts@Options{..} exe args inp = do + vLog opts $ intercalate " " $ map formatProcessArg (oGhcPkgProgram:args) + outp <- readProcess exe args inp + vLog opts $ unlines $ map ("=> "++) $ lines outp + return outp + +callProcessStderr' + :: Options -> Maybe FilePath -> FilePath -> [String] -> IO ExitCode +callProcessStderr' opts mwd exe args = do + let cd = case mwd of + Nothing -> []; Just wd -> [ "cd", formatProcessArg wd++";" ] + vLog opts $ intercalate " " $ cd ++ map formatProcessArg (exe:args) + (_, _, _, h) <- createProcess (proc exe args) { std_out = UseHandle stderr + , cwd = mwd } + waitForProcess h + +callProcessStderr :: Options -> Maybe FilePath -> FilePath -> [String] -> IO () +callProcessStderr opts mwd exe args = do + rv <- callProcessStderr' opts mwd exe args + case rv of + ExitSuccess -> return () + ExitFailure v -> processFailedException "callProcessStderr" exe args v + +processFailedException :: String -> String -> [String] -> Int -> IO a +processFailedException fn exe args rv = + ioError $ mkIOError OtherError msg Nothing Nothing + where + msg = concat [ fn, ": ", exe, " " + , intercalate " " (map formatProcessArg args) + , " (exit " ++ show rv ++ ")" + ] + +formatProcessArg :: String -> String +formatProcessArg xs + | any isSpace xs = "'"++ xs ++"'" + | otherwise = xs + +data HEAD = HEAD deriving (Eq, Show) + +installCabal :: Options -> Either HEAD Version -> IO (PackageDbDir, CabalVersion) +installCabal opts ever = do + appdir <- appCacheDir + let message ver = do + let sver = showVersion ver + hPutStr stderr $ printf "\ +\cabal-helper-wrapper: Installing a private copy of Cabal because we couldn't\n\ +\find the right version in your global/user package-db, this might take a\n\ +\while but will only happen once per Cabal version you're using.\n\ +\\n\ +\If anything goes horribly wrong just delete this directory and try again:\n\ +\ %s\n\ +\\n\ +\If you want to avoid this automatic installation altogether install\n\ +\version %s of Cabal manually (into your user or global package-db):\n\ +\ $ cabal install Cabal --constraint \"Cabal == %s\"\n\ +\\n\ +\Installing Cabal %s ...\n" appdir sver sver sver + + withSystemTempDirectory "cabal-helper-Cabal-source" $ \tmpdir -> do + (srcdir, cabalVer) <- case ever of + Left HEAD -> do + second CabalHEAD <$> unpackCabalHEAD opts tmpdir + Right ver -> do + message ver + let patch = fromMaybe nopCabalPatchDescription $ + find ((ver`elem`) . cpdVersions) patchyCabalVersions + (,) <$> unpackPatchedCabal opts ver tmpdir patch <*> pure (CabalVersion ver) + + db <- createPkgDb opts cabalVer + + runCabalInstall opts db srcdir ever + + return (db, cabalVer) + +{- +TODO: If the Cabal version we want to install is less than or equal to one we +have available, either through act-as-setup or in a package-db we should be able +to use act-as-setup or build a default Setup.hs exe and patch the Cabal source +to say build-type:simple. This will sidestep bugs in c-i>=1.24 + +See conversation in +https://github.com/haskell/cabal/commit/e2bf243300957321497353a2f85517e464f764ab + +Otherwise we might be able to use the shipped Setup.hs + +-} + +runCabalInstall + :: Options -> PackageDbDir -> CabalSourceDir -> Either HEAD Version-> IO () +runCabalInstall opts (PackageDbDir db) (CabalSourceDir srcdir) ever = do + civ@CabalInstallVersion {..} <- cabalInstallVersion opts + cabal_opts <- return $ concat + [ + [ "--package-db=clear" + , "--package-db=global" + , "--package-db=" ++ db + , "--prefix=" ++ db "prefix" + ] + , withGHCProgramOptions opts + , if cabalInstallVer >= Version [1,20,0,0] [] + then ["--no-require-sandbox"] + else [] + , [ "install", srcdir ] + , if oVerbose opts + then ["-v"] + else [] + , [ "--only-dependencies" ] + ] + + callProcessStderr opts (Just "/") (oCabalProgram opts) cabal_opts + + runSetupHs opts db srcdir ever civ + + hPutStrLn stderr "done" + +withGHCProgramOptions :: Options -> [String] +withGHCProgramOptions opts = + concat [ [ "--with-ghc=" ++ oGhcProgram opts ] + , if oGhcPkgProgram opts /= oGhcPkgProgram defaultOptions + then [ "--with-ghc-pkg=" ++ oGhcPkgProgram opts ] + else [] + ] + +runSetupHs + :: Options + -> FilePath + -> FilePath + -> Either HEAD Version + -> CabalInstallVersion + -> IO () +runSetupHs opts@Options {..} db srcdir ever CabalInstallVersion {..} + | cabalInstallVer >= parseVer "1.24" = do + go $ \args -> callProcessStderr opts (Just srcdir) oCabalProgram $ + [ "act-as-setup", "--" ] ++ args + | otherwise = do + SetupProgram {..} <- compileSetupHs opts db srcdir + go $ callProcessStderr opts (Just srcdir) setupProgram + where + parmake_opt :: Maybe Int -> [String] + parmake_opt nproc' + | Left _ <- ever = ["-j"++nproc] + | Right ver <- ever, ver >= Version [1,20] [] = ["-j"++nproc] + | otherwise = [] + where + nproc = fromMaybe "" $ show <$> nproc' + + go :: ([String] -> IO ()) -> IO () + go run = do + run $ [ "configure", "--package-db", db, "--prefix", db "prefix" ] + ++ withGHCProgramOptions opts + mnproc <- join . fmap readMaybe <$> lookupEnv "NPROC" + run $ [ "build" ] ++ parmake_opt mnproc + run [ "copy" ] + run [ "register" ] + + + + +newtype SetupProgram = SetupProgram { setupProgram :: FilePath } +compileSetupHs :: Options -> FilePath -> FilePath -> IO SetupProgram +compileSetupHs opts db srcdir = do + ver <- ghcVersion opts + let no_version_macros + | ver >= Version [8] [] = [ "-fno-version-macros" ] + | otherwise = [] + + file = srcdir "Setup" + + callProcessStderr opts (Just srcdir) (oGhcProgram opts) $ concat + [ [ "--make" + , "-package-conf", db + ] + , no_version_macros + , [ file <.> "hs" + , "-o", file + ] + ] + return $ SetupProgram file + +data CabalPatchDescription = CabalPatchDescription { + cpdVersions :: [Version], + cpdUnpackVariant :: UnpackCabalVariant, + cpdPatchFn :: FilePath -> IO () + } +nopCabalPatchDescription :: CabalPatchDescription +nopCabalPatchDescription = CabalPatchDescription [] LatestRevision (const (return ())) + +patchyCabalVersions :: [CabalPatchDescription] +patchyCabalVersions = [ + let versions = [ Version [1,18,1] [] ] + variant = Pristine + patch = fixArrayConstraint + in CabalPatchDescription versions variant patch, + + let versions = [ Version [1,18,0] [] ] + variant = Pristine + patch dir = do + fixArrayConstraint dir + fixOrphanInstance dir + in CabalPatchDescription versions variant patch, + + let versions = [ Version [1,24,1,0] [] ] + variant = Pristine + patch _ = return () + in CabalPatchDescription versions variant patch + ] + where + fixArrayConstraint dir = do + let cabalFile = dir "Cabal.cabal" + cabalFileTmp = cabalFile ++ ".tmp" + + cf <- readFile cabalFile + writeFile cabalFileTmp $ replace "&& < 0.5" "&& < 0.6" cf + renameFile cabalFileTmp cabalFile + + fixOrphanInstance dir = do + let versionFile = dir "Distribution/Version.hs" + versionFileTmp = versionFile ++ ".tmp" + + let languagePragma = + "{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}" + languagePragmaCPP = + "{-# LANGUAGE CPP, DeriveDataTypeable, StandaloneDeriving #-}" + + derivingDataVersion = + "deriving instance Data Version" + derivingDataVersionCPP = unlines [ + "#if __GLASGOW_HASKELL__ < 707", + derivingDataVersion, + "#endif" + ] + + vf <- readFile versionFile + writeFile versionFileTmp + $ replace derivingDataVersion derivingDataVersionCPP + $ replace languagePragma languagePragmaCPP vf + + renameFile versionFileTmp versionFile + +unpackPatchedCabal + :: Options + -> Version + -> FilePath + -> CabalPatchDescription + -> IO CabalSourceDir +unpackPatchedCabal opts cabalVer tmpdir (CabalPatchDescription _ variant patch) = do + res@(CabalSourceDir dir) <- unpackCabal opts cabalVer tmpdir variant + patch dir + return res + +data UnpackCabalVariant = Pristine | LatestRevision +newtype CabalSourceDir = CabalSourceDir { unCabalSourceDir :: FilePath } +unpackCabal + :: Options -> Version -> FilePath -> UnpackCabalVariant -> IO CabalSourceDir +unpackCabal opts cabalVer tmpdir variant = do + let cabal = "Cabal-" ++ showVersion cabalVer + dir = tmpdir cabal + variant_opts = case variant of Pristine -> [ "--pristine" ]; _ -> [] + args = [ "get", cabal ] ++ variant_opts + callProcessStderr opts (Just tmpdir) (oCabalProgram opts) args + return $ CabalSourceDir dir + +unpackCabalHEAD :: Options -> FilePath -> IO (CabalSourceDir, CommitId) +unpackCabalHEAD opts tmpdir = do + let dir = tmpdir "cabal-head.git" + url = "https://github.com/haskell/cabal.git" + ExitSuccess <- rawSystem "git" [ "clone", "--depth=1", url, dir] + commit <- + withDirectory_ dir $ trim <$> readProcess' opts "git" ["rev-parse", "HEAD"] "" + return (CabalSourceDir $ dir "Cabal", CommitId commit) + where + withDirectory_ :: FilePath -> IO a -> IO a + withDirectory_ dir action = + bracket + (liftIO getCurrentDirectory) + (liftIO . setCurrentDirectory) + (\_ -> liftIO (setCurrentDirectory dir) >> action) + +errorInstallCabal :: Version -> FilePath -> IO a +errorInstallCabal cabalVer _distdir = panicIO $ printf "\ +\Installing Cabal version %s failed.\n\ +\\n\ +\You have the following choices to fix this:\n\ +\\n\ +\- The easiest way to try and fix this is just reconfigure the project and try\n\ +\ again:\n\ +\ $ cabal clean && cabal configure\n\ +\\n\ +\- If that fails you can try to install the version of Cabal mentioned above\n\ +\ into your global/user package-db somehow, you'll probably have to fix\n\ +\ something otherwise it wouldn't have failed above:\n\ +\ $ cabal install Cabal --constraint 'Cabal == %s'\n\ +\\n\ +\- If you're using `Build-Type: Simple`:\n\ +\ - You can see if you can reinstall your cabal-install executable while\n\ +\ having it linked to a version of Cabal that's available in you\n\ +\ package-dbs or can be built automatically:\n\ +\ $ ghc-pkg list | grep Cabal # find an available Cabal version\n\ +\ Cabal-W.X.Y.Z\n\ +\ $ cabal install cabal-install --constraint 'Cabal == W.X.*'\n\ +\ Afterwards you'll have to reconfigure your project:\n\ +\ $ cabal clean && cabal configure\n\ +\\n\ +\- If you're using `Build-Type: Custom`:\n\ +\ - Have cabal-install rebuild your Setup.hs executable with a version of the\n\ +\ Cabal library that you have available in your global/user package-db:\n\ +\ $ cabal clean && cabal configure\n\ +\ You might also have to install some version of the Cabal to do this:\n\ +\ $ cabal install Cabal\n\ +\\n" sver sver + where + sver = showVersion cabalVer + +listCabalVersions :: Options -> MaybeT IO [Version] +listCabalVersions opts = listCabalVersions' opts Nothing + +listCabalVersions' :: Options -> Maybe PackageDbDir -> MaybeT IO [Version] +listCabalVersions' opts@Options {..} mdb = do + case mdb of + Nothing -> mzero + Just (PackageDbDir db_path) -> do + exists <- liftIO $ doesDirectoryExist db_path + case exists of + False -> mzero + True -> MaybeT $ logIOError opts "listCabalVersions'" $ Just <$> do + let mdbopt = ("--package-conf="++) <$> unPackageDbDir <$> mdb + args = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt + + catMaybes . map (fmap snd . parsePkgId . fromString) . words + <$> readProcess' opts oGhcPkgProgram args "" + +cabalVersionExistsInPkgDb :: Options -> Version -> PackageDbDir -> IO Bool +cabalVersionExistsInPkgDb opts cabalVer db@(PackageDbDir db_path) = do + exists <- doesDirectoryExist db_path + case exists of + False -> return False + True -> fromMaybe False <$> runMaybeT (do + vers <- listCabalVersions' opts (Just db) + return $ cabalVer `elem` vers) + +ghcVersion :: Options -> IO Version +ghcVersion opts@Options {..} = do + parseVer . trim <$> readProcess' opts oGhcProgram ["--numeric-version"] "" + +ghcPkgVersion :: Options -> IO Version +ghcPkgVersion opts@Options {..} = do + parseVer . trim . dropWhile (not . isDigit) <$> readProcess' opts oGhcPkgProgram ["--version"] "" + +newtype CabalInstallVersion = CabalInstallVersion { cabalInstallVer :: Version } +cabalInstallVersion :: Options -> IO CabalInstallVersion +cabalInstallVersion opts@Options {..} = do + CabalInstallVersion . parseVer . trim + <$> readProcess' opts oCabalProgram ["--numeric-version"] "" + +createPkgDb :: Options -> CabalVersion -> IO PackageDbDir +createPkgDb opts@Options {..} cabalVer = do + db@(PackageDbDir db_path) <- getPrivateCabalPkgDb opts cabalVer + exists <- doesDirectoryExist db_path + when (not exists) $ callProcessStderr opts Nothing oGhcPkgProgram ["init", db_path] + return db + +getPrivateCabalPkgDb :: Options -> CabalVersion -> IO PackageDbDir +getPrivateCabalPkgDb opts cabalVer = do + appdir <- appCacheDir + ghcVer <- ghcVersion opts + let db_path = appdir exeName cabalVer + ++ "-ghc" ++ showVersion ghcVer + ++ ".package-db" + return $ PackageDbDir db_path + +-- "Cabal" ++ ver ++ "-ghc" ++ showVersion ghcVer + +-- | Find @version: XXX@ delcaration in a cabal file +cabalFileVersion :: String -> Version +cabalFileVersion = parseVer . cabalFileTopField "version" + +-- | Find @build-type: XXX@ delcaration in a cabal file +cabalFileBuildType :: String -> String +cabalFileBuildType = cabalFileTopField "build-type" + +cabalFileTopField :: String -> String -> String +cabalFileTopField field cabalFile = value + where + Just value = extract <$> find ((field++":") `isPrefixOf`) ls + ls = map (map toLower) $ lines cabalFile + extract = dropWhile (/=':') >>> drop 1 >>> dropWhile isSpace >>> takeWhile (not . isSpace) diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Data.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Data.hs new file mode 100644 index 0000000..80df962 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Data.hs @@ -0,0 +1,81 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2017 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-} +{-# OPTIONS_GHC -fforce-recomp #-} + +{-| +Module : CabalHelper.Compiletime.Data +Description : Embeds source code for runtime component using TH +License : GPL-3 +-} + +module CabalHelper.Compiletime.Data where + +import Control.Monad +import Control.Monad.IO.Class +import Data.Functor +import qualified Data.ByteString as BS +import qualified Data.ByteString.UTF8 as UTF8 +import Language.Haskell.TH +import System.Directory +import System.FilePath +import System.IO.Temp +import System.PosixCompat.Files +import System.PosixCompat.Time +import System.PosixCompat.Types +import Prelude + +import CabalHelper.Compiletime.Compat.Environment + +withSystemTempDirectoryEnv :: String -> (FilePath -> IO b) -> IO b +withSystemTempDirectoryEnv tpl f = do + m <- liftIO $ lookupEnv "CABAL_HELPER_KEEP_SOURCEDIR" + case m of + Nothing -> withSystemTempDirectory tpl f + Just _ -> do + tmpdir <- getCanonicalTemporaryDirectory + f =<< createTempDirectory tmpdir tpl + +createHelperSources :: FilePath -> IO () +createHelperSources dir = do + let chdir = dir "CabalHelper" + liftIO $ do + createDirectoryIfMissing True $ chdir "Runtime" + createDirectoryIfMissing True $ chdir "Shared" + + let modtime :: EpochTime + modtime = fromIntegral $ (read :: String -> Integer) + -- See https://reproducible-builds.org/specs/source-date-epoch/ + $(runIO $ do + msde :: Maybe Integer + <- fmap read <$> lookupEnv "SOURCE_DATE_EPOCH" + (current_time :: Integer) <- round . toRational <$> epochTime + return $ LitE . StringL $ show $ maybe current_time id msde) + + liftIO $ forM_ sourceFiles $ \(fn, src) -> do + let path = chdir fn + BS.writeFile path $ UTF8.fromString src + setFileTimes path modtime modtime + + +sourceFiles :: [(FilePath, String)] +sourceFiles = + [ ("Runtime/Main.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Runtime/Main.hs"))) + , ("Shared/Common.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Shared/Common.hs"))) + , ("Shared/Sandbox.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Shared/Sandbox.hs"))) + , ("Shared/InterfaceTypes.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Shared/InterfaceTypes.hs"))) + ] diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Log.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Log.hs new file mode 100644 index 0000000..a329c54 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Log.hs @@ -0,0 +1,45 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2017-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE ScopedTypeVariables #-} + +{-| +Module : CabalHelper.Compiletime.Log +Description : Basic logging facilities +License : GPL-3 +-} + +module CabalHelper.Compiletime.Log where + +import Control.Monad +import Control.Monad.IO.Class +import Control.Exception as E +import Data.String +import System.IO +import Prelude + +import CabalHelper.Compiletime.Types + +vLog :: MonadIO m => Options -> String -> m () +vLog Options { oVerbose = True } msg = + liftIO $ hPutStrLn stderr msg +vLog _ _ = return () + +logIOError :: Options -> String -> IO (Maybe a) -> IO (Maybe a) +logIOError opts label a = do + a `E.catch` \(ex :: IOError) -> do + vLog opts $ label ++ ": " ++ show ex + return Nothing diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Types.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Types.hs new file mode 100644 index 0000000..77c3255 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Types.hs @@ -0,0 +1,42 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DefaultSignatures #-} + +{-| +Module : CabalHelper.Compiletime.Types +Description : Types used throughout +License : GPL-3 +-} + +module CabalHelper.Compiletime.Types where + +import Data.Version + +data Options = Options { + oHelp :: Bool + , oVerbose :: Bool + , oGhcProgram :: FilePath + , oGhcPkgProgram :: FilePath + , oCabalProgram :: FilePath + , oCabalVersion :: Maybe Version + , oCabalPkgDb :: Maybe PackageDbDir +} + +newtype PackageDbDir = PackageDbDir { unPackageDbDir :: FilePath } + +defaultOptions :: Options +defaultOptions = Options False False "ghc" "ghc-pkg" "cabal" Nothing Nothing diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Wrapper.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Wrapper.hs new file mode 100644 index 0000000..461ef96 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Compiletime/Wrapper.hs @@ -0,0 +1,227 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +{-# LANGUAGE RecordWildCards, NamedFieldPuns, FlexibleContexts, ViewPatterns #-} +module Main where + +import Cabal.Plan +import Control.Applicative +import Control.Monad +import Data.Char +import Data.List +import Data.Maybe +import Data.String +import Text.Printf +import Text.Show.Pretty +import System.Console.GetOpt +import System.Environment +import System.Directory +import System.FilePath +import System.Process +import System.Exit +import System.IO +import Prelude + +import qualified Data.Text as Text +import qualified Data.Map.Strict as Map + +import Distribution.System (buildPlatform) +import Distribution.Text (display) +import Distribution.Verbosity (silent, deafening) +import Distribution.Package (packageName, packageVersion) +import Distribution.Simple.GHC as GHC (configure) + +import Paths_cabal_helper (version) +import CabalHelper.Compiletime.Compat.ProgramDb + ( defaultProgramDb, programPath, lookupProgram, ghcProgram, ghcPkgProgram) +import CabalHelper.Compiletime.Compat.Version +import CabalHelper.Compiletime.Compile +import CabalHelper.Compiletime.Types +import CabalHelper.Shared.Common +import CabalHelper.Shared.InterfaceTypes + +usage :: IO () +usage = do + prog <- getProgName + hPutStr stderr $ "Usage: " ++ prog ++ " " ++ usageMsg + where + usageMsg = "\ +\( print-appcachedir\n\ +\| print-build-platform\n\ +\| [--verbose]\n\ +\ [--with-ghc=GHC_PATH]\n\ +\ [--with-ghc-pkg=GHC_PKG_PATH]\n\ +\ [--with-cabal=CABAL_PATH]\n\ +\ [--with-cabal-version=VERSION]\n\ +\ [--with-cabal-pkg-db=PKG_DB]\n\ +\ v1-style PROJ_DIR DIST_DIR \n\ +\ ( print-exe | package-id | [CABAL_HELPER_ARGS...] )\n\ +\ v2-style PROJ_DIR DIST_NEWSTYLE_DIR DIST_DIR\n\ +\ ( print-exe | package-id | [CABAL_HELPER_ARGS...] )\n\ +\)\n" + +globalArgSpec :: [OptDescr (Options -> Options)] +globalArgSpec = + [ option "h" ["help"] "Display help message" $ + NoArg $ \o -> o { oHelp = True } + , option "" ["verbose"] "Be more verbose" $ + NoArg $ \o -> o { oVerbose = True } + + , option "" ["with-ghc"] "GHC executable to use" $ + reqArg "PROG" $ \p o -> o { oGhcProgram = p } + + , option "" ["with-ghc-pkg"] "ghc-pkg executable to use (only needed when guessing from GHC path fails)" $ + reqArg "PROG" $ \p o -> o { oGhcPkgProgram = p } + + , option "" ["with-cabal"] "cabal-install executable to use" $ + reqArg "PROG" $ \p o -> o { oCabalProgram = p } + + , option "" ["with-cabal-version"] "Cabal library version to use" $ + reqArg "VERSION" $ \p o -> o { oCabalVersion = Just $ parseVer p } + + , option "" ["with-cabal-pkg-db"] "package database to look for Cabal library in" $ + reqArg "PKG_DB" $ \p o -> o { oCabalPkgDb = Just (PackageDbDir p) } + + ] + where + option :: [Char] -> [String] -> String -> ArgDescr a -> OptDescr a + option s l udsc dsc = Option s l dsc udsc + + reqArg :: String -> (String -> a) -> ArgDescr a + reqArg udsc dsc = ReqArg dsc udsc + +parseCommandArgs :: Options -> [String] -> (Options, [String]) +parseCommandArgs opts argv + = case getOpt RequireOrder globalArgSpec argv of + (o,r,[]) -> (foldr id opts o, r) + (_,_,errs) -> + panic $ "Parsing command options failed:\n" ++ concat errs + +guessProgramPaths :: Options -> IO Options +guessProgramPaths opts = do + let v | oVerbose opts = deafening + | otherwise = silent + + mGhcPath0 | same oGhcProgram opts dopts = Nothing + | otherwise = Just $ oGhcProgram opts + mGhcPkgPath0 | same oGhcPkgProgram opts dopts = Nothing + | otherwise = Just $ oGhcPkgProgram opts + + (_compiler, _mplatform, progdb) + <- GHC.configure + v + mGhcPath0 + mGhcPkgPath0 + defaultProgramDb + + let mghcPath1 = programPath <$> lookupProgram ghcProgram progdb + mghcPkgPath1 = programPath <$> lookupProgram ghcPkgProgram progdb + + return $ opts { oGhcProgram = fromMaybe (oGhcProgram opts) mghcPath1 + , oGhcPkgProgram = fromMaybe (oGhcProgram opts) mghcPkgPath1 + } + where + same f o o' = f o == f o' + dopts = defaultOptions + +overrideVerbosityEnvVar :: Options -> IO Options +overrideVerbosityEnvVar opts = do + x <- lookup "CABAL_HELPER_DEBUG" <$> getEnvironment + return $ case x of + Just _ -> opts { oVerbose = True } + Nothing -> opts + +main :: IO () +main = handlePanic $ do + (opts', args) <- parseCommandArgs defaultOptions <$> getArgs + opts <- overrideVerbosityEnvVar =<< guessProgramPaths opts' + case args of + _ | oHelp opts -> usage + [] -> usage + "help":[] -> usage + "version":[] -> putStrLn $ showVersion version + "print-appdatadir":[] -> putStrLn =<< appCacheDir + "print-appcachedir":[] -> putStrLn =<< appCacheDir + "print-build-platform":[] -> putStrLn $ display buildPlatform + + _:projdir:_distdir:"package-id":[] -> do + let v | oVerbose opts = deafening + | otherwise = silent + -- ghc-mod will catch multiple cabal files existing before we get here + [cfile] <- filter isCabalFile <$> getDirectoryContents projdir + gpd <- readPackageDescription v (projdir cfile) + putStrLn $ show $ + [Just $ ChResponseVersion (display (packageName gpd)) (toDataVersion $ packageVersion gpd)] + + "v2-style":projdir:distdir_newstyle:unitid':args' -> do + let unitid = UnitId $ Text.pack unitid' + let plan_path = distdir_newstyle "cache" "plan.json" + plan@PlanJson {pjCabalLibVersion=Ver (makeDataVersion -> pjCabalLibVersion) } + <- decodePlanJson plan_path + case oCabalVersion opts of + Just ver | pjCabalLibVersion /= ver -> let + sver = showVersion ver + spjVer = showVersion pjCabalLibVersion + in panic $ printf "\ +\Cabal version %s was requested but plan.json was written by version %s" sver spjVer + _ -> case Map.lookup unitid $ pjUnits plan of + Just u@Unit {uType} | uType /= UnitTypeLocal -> do + panic $ "\ +\UnitId '"++ unitid' ++"' points to non-local unit: " ++ ppShow u + Just Unit {uDistDir=Nothing} -> panic $ printf "\ +\plan.json doesn't contain 'dist-dir' for UnitId '"++ unitid' ++"'" + Just Unit {uType=UnitTypeLocal, uDistDir=Just distdir} -> + runHelper opts projdir (Just (plan, distdir_newstyle)) distdir pjCabalLibVersion args' + _ -> let + units = map (\(UnitId u) -> Text.unpack u) + $ Map.keys + $ Map.filter ((==UnitTypeLocal) . uType) + $ pjUnits plan + + units_list = unlines $ map (" "++) units + in + panic $ "\ +\UnitId '"++ unitid' ++"' not found in plan.json, available local units:\n" ++ units_list + + "v1-style":projdir:distdir:args' -> do + cfgf <- canonicalizePath (distdir "setup-config") + mhdr <- getCabalConfigHeader cfgf + case (mhdr, oCabalVersion opts) of + (Nothing, _) -> panic $ printf "\ +\Could not read Cabal's persistent setup configuration header\n\ +\- Check first line of: %s\n\ +\- Maybe try: $ cabal configure" cfgf + (Just (hdrCabalVersion, _), Just ver) + | hdrCabalVersion /= ver -> panic $ printf "\ +\Cabal version %s was requested but setup configuration was\n\ +\written by version %s" (showVersion ver) (showVersion hdrCabalVersion) + (Just (hdrCabalVersion, _), _) -> + runHelper opts projdir Nothing distdir hdrCabalVersion args' + _ -> do + hPutStrLn stderr "Invalid command line!" + usage + exitWith $ ExitFailure 1 + +runHelper :: Options -> FilePath -> Maybe (PlanJson, FilePath) -> FilePath -> DataVersion -> [String] -> IO () +runHelper opts projdir mnewstyle distdir cabal_ver args' = do + eexe <- compileHelper opts cabal_ver projdir mnewstyle distdir + case eexe of + Left e -> exitWith e + Right exe -> do + case args' of + "print-exe":_ -> putStrLn exe + _ -> do + (_,_,_,h) <- createProcess $ proc exe $ projdir : distdir : args' + exitWith =<< waitForProcess h diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Runtime/Main.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Runtime/Main.hs new file mode 100644 index 0000000..78260f8 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Runtime/Main.hs @@ -0,0 +1,841 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP, BangPatterns, RecordWildCards, RankNTypes, ViewPatterns #-} + +#ifdef MIN_VERSION_Cabal +#undef CH_MIN_VERSION_Cabal +#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal +#endif + +import Distribution.Simple.Utils (cabalVersion) +import Distribution.Simple.Configure +import Distribution.Package + ( PackageIdentifier + , InstalledPackageId + , PackageId + , packageName + , packageVersion + ) +import Distribution.PackageDescription + ( PackageDescription + , GenericPackageDescription(..) + , Flag(..) + , FlagName(..) + , FlagAssignment + , Executable(..) + , Library(..) + , TestSuite(..) + , Benchmark(..) + , BuildInfo(..) + , TestSuiteInterface(..) + , BenchmarkInterface(..) + , withLib + ) +import Distribution.PackageDescription.Configuration + ( flattenPackageDescription + ) +import Distribution.Simple.Program + ( requireProgram + , ghcProgram + ) +import Distribution.Simple.Program.Types + ( ConfiguredProgram(..) + ) +import Distribution.Simple.Configure + ( getPersistBuildConfig + ) +import Distribution.Simple.LocalBuildInfo + ( LocalBuildInfo(..) + , Component(..) + , ComponentName(..) + , ComponentLocalBuildInfo(..) + , componentBuildInfo + , externalPackageDeps + , withComponentsLBI + , withLibLBI + , withExeLBI + ) +import Distribution.Simple.GHC + ( componentGhcOptions + ) +import Distribution.Simple.Program.GHC + ( GhcOptions(..) + , renderGhcOptions + ) +import Distribution.Simple.Setup + ( ConfigFlags(..) + , Flag(..) + , fromFlagOrDefault + ) +import Distribution.Simple.Build + ( initialBuildSteps + ) +import Distribution.Simple.BuildPaths + ( autogenModuleName + , cppHeaderName + ) +import Distribution.Simple.Compiler + ( PackageDB(..) + , compilerId + ) +import Distribution.Compiler + ( CompilerId(..) + ) +import Distribution.ModuleName + ( components + ) +import qualified Distribution.ModuleName as C + ( ModuleName + ) +import Distribution.Text + ( display + ) +import Distribution.Verbosity + ( Verbosity + , silent + , deafening + , normal + ) +import Distribution.Version + ( Version + ) + +#if CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 +import Distribution.Utils.NubList +#endif + +#if CH_MIN_VERSION_Cabal(1,23,0) +-- >= 1.23 +import Distribution.Simple.LocalBuildInfo + ( localUnitId + ) +#else +-- <= 1.22 +import Distribution.Simple.LocalBuildInfo + ( inplacePackageId + ) +#endif + +#if CH_MIN_VERSION_Cabal(1,25,0) +-- >=1.25 +import Distribution.PackageDescription + ( unFlagName + -- , mkFlagName + ) +import Distribution.Types.ForeignLib + ( ForeignLib(..) + ) +import Distribution.Types.UnqualComponentName + ( unUnqualComponentName + ) +#endif + +#if CH_MIN_VERSION_Cabal(2,0,0) +-- CPP >= 2.0 +import Distribution.Simple.LocalBuildInfo + ( allLibModules + , componentBuildDir + ) +import Distribution.Simple.Register + ( internalPackageDBPath + ) +import Distribution.Backpack + ( OpenUnitId(..), + OpenModule(..) + ) +import Distribution.ModuleName + ( ModuleName + ) +import Distribution.Types.ComponentId + ( unComponentId + ) +import Distribution.Types.ComponentLocalBuildInfo + ( maybeComponentInstantiatedWith + ) +import Distribution.Types.ModuleRenaming + ( ModuleRenaming(..), + isDefaultRenaming + ) +import Distribution.Types.MungedPackageId + ( MungedPackageId + ) +import Distribution.Types.UnitId + ( UnitId + , unDefUnitId + , unUnitId + ) +import Distribution.Types.UnitId + ( DefUnitId + ) +import Distribution.Utils.NubList + ( toNubListR + ) +import Distribution.Version + ( versionNumbers + , mkVersion + ) +import qualified Distribution.InstalledPackageInfo as Installed +#endif + +#if CH_MIN_VERSION_Cabal(2,2,0) +import Distribution.Types.GenericPackageDescription + ( unFlagAssignment + ) +#endif + +import Control.Applicative ((<$>)) +import Control.Arrow (first, second, (&&&)) +import Control.Monad +import Control.Exception (catch, PatternMatchFail(..)) +import Data.List +import qualified Data.Map as Map +import Data.Maybe +import Data.Monoid +import Data.IORef +import qualified Data.Version as DataVersion +import System.Environment +import System.Directory +import System.FilePath +import System.Exit +import System.IO +import System.IO.Unsafe (unsafeInterleaveIO, unsafePerformIO) +import Text.Printf + +import CabalHelper.Shared.Sandbox +import CabalHelper.Shared.Common +import CabalHelper.Shared.InterfaceTypes + +usage :: IO () +usage = do + prog <- getProgName + hPutStr stderr $ "Usage: " ++ prog ++ " " ++ usageMsg + where + usageMsg = "" + ++"PROJ_DIR DIST_DIR [--with-* ...] (\n" + ++" version\n" + ++" | print-lbi [--human]\n" + ++" | package-id\n" + ++" | flags\n" + ++" | config-flags\n" + ++" | non-default-config-flags\n" + ++" | write-autogen-files\n" + ++" | compiler-version\n" + ++" | ghc-options [--with-inplace]\n" + ++" | ghc-src-options [--with-inplace]\n" + ++" | ghc-pkg-options [--with-inplace]\n" + ++" | ghc-merged-pkg-options [--with-inplace]\n" + ++" | ghc-lang-options [--with-inplace]\n" + ++" | package-db-stack\n" + ++" | entrypoints\n" + ++" | needs-build-output\n" + ++" | source-dirs\n" + ++" ) ...\n" + +commands :: [String] +commands = [ "print-lbi" + , "package-id" + , "flags" + , "config-flags" + , "non-default-config-flags" + , "write-autogen-files" + , "compiler-version" + , "ghc-options" + , "ghc-src-options" + , "ghc-pkg-options" + , "ghc-lang-options" + , "package-db-stack" + , "entrypoints" + , "needs-build-output" + , "source-dirs" + ] + +main :: IO () +main = do + args <- getArgs + + projdir:distdir:args' <- case args of + [] -> usage >> exitFailure + _ -> return args + + ddexists <- doesDirectoryExist distdir + when (not ddexists) $ do + errMsg $ "distdir '"++distdir++"' does not exist" + exitFailure + + [cfile] <- filter isCabalFile <$> getDirectoryContents projdir + + v <- maybe silent (const deafening) . lookup "CABAL_HELPER_DEBUG" <$> getEnvironment + lbi <- unsafeInterleaveIO $ getPersistBuildConfig distdir + gpd <- unsafeInterleaveIO $ readPackageDescription v (projdir cfile) + let pd = localPkgDescr lbi + let lvd = (lbi, v, distdir) + + let + -- a =<< b $$ c == (a =<< b) $$ c + infixr 2 $$ + ($$) = ($) + + collectCmdOptions :: [String] -> [[String]] + collectCmdOptions = + reverse . map reverse . foldl f [] . dropWhile isOpt + where + isOpt = ("--" `isPrefixOf`) + f [] x = [[x]] + f (a:as) x + | isOpt x = (x:a):as + | otherwise = [x]:(a:as) + + let cmds = collectCmdOptions args' + + if any (["version"] `isPrefixOf`) cmds + then do + putStrLn $ + printf "using version %s of the Cabal library" (display cabalVersion) + exitSuccess + else return () + + print =<< flip mapM cmds $$ \x -> do + case x of + "flags":[] -> do + return $ Just $ ChResponseFlags $ sort $ + map (flagName' &&& flagDefault) $ genPackageFlags gpd + + "config-flags":[] -> do + return $ Just $ ChResponseFlags $ sort $ + map (first unFlagName) +#if CH_MIN_VERSION_Cabal(2,2,0) + $ unFlagAssignment $ configConfigurationsFlags +#else + $ configConfigurationsFlags +#endif + $ configFlags lbi + + "non-default-config-flags":[] -> do + let flagDefinitons = genPackageFlags gpd + flagAssgnments = +#if CH_MIN_VERSION_Cabal(2,2,0) + unFlagAssignment $ configConfigurationsFlags +#else + configConfigurationsFlags +#endif + $ configFlags lbi + nonDefaultFlags = + [ (flag_name, val) + | MkFlag {flagName=(unFlagName -> flag_name'), flagDefault=def_val} <- flagDefinitons + , (unFlagName -> flag_name, val) <- flagAssgnments + , flag_name == flag_name' + , val /= def_val + ] + return $ Just $ ChResponseFlags $ sort nonDefaultFlags + + "write-autogen-files":[] -> do + initialBuildStepsForAllComponents distdir pd lbi v + return Nothing + + "compiler-version":[] -> do + let CompilerId comp ver = compilerId $ compiler lbi + return $ Just $ ChResponseVersion (show comp) (toDataVersion ver) + + "ghc-options":flags -> do + res <- componentOptions lvd True flags id + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "ghc-src-options":flags -> do + res <- componentOptions lvd False flags $ \opts -> mempty { + -- Not really needed but "unexpected package db stack: []" + ghcOptPackageDBs = [GlobalPackageDB, UserPackageDB], + + ghcOptCppOptions = ghcOptCppOptions opts, + ghcOptCppIncludePath = ghcOptCppIncludePath opts, + ghcOptCppIncludes = ghcOptCppIncludes opts, + ghcOptFfiIncludes = ghcOptFfiIncludes opts, + ghcOptSourcePathClear = ghcOptSourcePathClear opts, + ghcOptSourcePath = ghcOptSourcePath opts + } + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "ghc-pkg-options":flags -> do + res <- componentOptions lvd True flags $ \opts -> mempty { + ghcOptPackageDBs = ghcOptPackageDBs opts, + ghcOptPackages = ghcOptPackages opts, + ghcOptHideAllPackages = ghcOptHideAllPackages opts + } + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "ghc-merged-pkg-options":flags -> do + res <- mconcat . map snd <$> (componentOptions' lvd True flags (\_ _ o -> return o) $ \opts -> mempty { + ghcOptPackageDBs = [], + ghcOptHideAllPackages = NoFlag, + ghcOptPackages = ghcOptPackages opts + }) + + let res' = nubPackageFlags $ res { ghcOptPackageDBs = withPackageDB lbi + , ghcOptHideAllPackages = Flag True + } + + Just . ChResponseList <$> renderGhcOptions' lbi v res' + + "ghc-lang-options":flags -> do + res <- componentOptions lvd False flags $ \opts -> mempty { + ghcOptPackageDBs = [GlobalPackageDB, UserPackageDB], + + ghcOptLanguage = ghcOptLanguage opts, + ghcOptExtensions = ghcOptExtensions opts, + ghcOptExtensionMap = ghcOptExtensionMap opts + } + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "package-db-stack":[] -> do + let + pkgDb GlobalPackageDB = ChPkgGlobal + pkgDb UserPackageDB = ChPkgUser + pkgDb (SpecificPackageDB s) = ChPkgSpecific s + + -- TODO: Setup.hs has access to the sandbox as well: ghc-mod#478 + return $ Just $ ChResponsePkgDbs $ map pkgDb $ withPackageDB lbi + + "entrypoints":[] -> do +#if CH_MIN_VERSION_Cabal(2,0,0) + includeDirMap <- recursiveDepInfo lbi v distdir + eps <- componentsMap lbi v distdir $ \c clbi _bi -> do + case needsBuildOutput includeDirMap (componentUnitId clbi) of + ProduceBuildOutput -> return $ componentEntrypoints c + NoBuildOutput -> return seps + where (_,_,seps) = recursiveIncludeDirs includeDirMap (componentUnitId clbi) +#else + eps <- componentsMap lbi v distdir $ \c _clbi _bi -> + return $ componentEntrypoints c +#endif + -- MUST append Setup component at the end otherwise CabalHelper gets + -- confused + let eps' = eps ++ [(ChSetupHsName, ChSetupEntrypoint)] + return $ Just $ ChResponseEntrypoints eps' + + "needs-build-output":[] -> do +#if CH_MIN_VERSION_Cabal(2,0,0) + includeDirMap <- recursiveDepInfo lbi v distdir + nbs <- componentsMap lbi v distdir $ \c clbi _bi -> + return $ needsBuildOutput includeDirMap (componentUnitId clbi) +#else + nbs <- componentsMap lbi v distdir $ \c _clbi _bi -> + return $ NoBuildOutput +#endif + return $ Just $ ChResponseNeedsBuild nbs + + "source-dirs":[] -> do + res <- componentsMap lbi v distdir $$ \_ _ bi -> return $ hsSourceDirs bi + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "print-lbi":flags -> + case flags of + ["--human"] -> print lbi >> return Nothing + [] -> return $ Just $ ChResponseLbi $ show lbi + + cmd:_ | not (cmd `elem` commands) -> + errMsg ("Unknown command: " ++ cmd) >> usage >> exitFailure + _ -> + errMsg "Invalid usage!" >> usage >> exitFailure + +flagName' = unFlagName . flagName + +-- getLibrary :: PackageDescription -> Library +-- getLibrary pd = unsafePerformIO $ do +-- lr <- newIORef (error "libraryMap: empty IORef") +-- withLib pd (writeIORef lr) +-- readIORef lr + +getLibraryClbi pd lbi = unsafePerformIO $ do + lr <- newIORef Nothing + + withLibLBI pd lbi $ \ lib clbi -> + writeIORef lr $ Just (lib,clbi) + + readIORef lr + + +getExeClbi pd lbi = unsafePerformIO $ do + lr <- newIORef Nothing + + withExeLBI pd lbi $ \ exe clbi -> + writeIORef lr $ Just (exe,clbi) + + readIORef lr + + +componentsMap :: LocalBuildInfo + -> Verbosity + -> FilePath + -> ( Component + -> ComponentLocalBuildInfo + -> BuildInfo + -> IO a) + -> IO [(ChComponentName, a)] +componentsMap lbi _v _distdir f = do + let pd = localPkgDescr lbi + + lr <- newIORef [] + + -- withComponentsLBI is deprecated but also exists in very old versions + -- it's equivalent to withAllComponentsInBuildOrder in newer versions + withComponentsLBI pd lbi $ \c clbi -> do + let bi = componentBuildInfo c + name = componentNameFromComponent c + + l' <- readIORef lr + r <- f c clbi bi +#if CH_MIN_VERSION_Cabal(2,0,0) + writeIORef lr $ (componentNameToCh (unUnitId $ componentUnitId clbi) name, r):l' +#else + writeIORef lr $ (componentNameToCh "" name, r):l' +#endif + + reverse <$> readIORef lr + +componentOptions' (lbi, v, distdir) inplaceFlag flags rf f = do + let pd = localPkgDescr lbi +#if CH_MIN_VERSION_Cabal(2,0,0) + includeDirMap <- recursiveDepInfo lbi v distdir +#endif + + componentsMap lbi v distdir $ \c clbi bi -> + let + outdir = componentOutDir lbi c + (clbi', adopts) = case flags of + _ | not inplaceFlag -> (clbi, mempty) + ["--with-inplace"] -> (clbi, mempty) +#if CH_MIN_VERSION_Cabal(2,0,0) + [] -> removeInplaceDeps v lbi pd clbi includeDirMap +#else + [] -> removeInplaceDeps v lbi pd clbi +#endif + opts = componentGhcOptions normal lbi bi clbi' outdir + opts' = f opts + + in rf lbi v $ nubPackageFlags $ opts' `mappend` adopts + +componentOptions (lbi, v, distdir) inplaceFlag flags f = + componentOptions' (lbi, v, distdir) inplaceFlag flags renderGhcOptions' f + +gmModuleName :: C.ModuleName -> ChModuleName +gmModuleName = ChModuleName . intercalate "." . components + +#if CH_MIN_VERSION_Cabal(2,0,0) +removeInplaceDeps :: Verbosity + -> LocalBuildInfo + -> PackageDescription + -> ComponentLocalBuildInfo + -> Map.Map UnitId SubDeps + -> (ComponentLocalBuildInfo, GhcOptions) +removeInplaceDeps _v lbi pd clbi includeDirs = let + removeInplace c = + let + (ideps, incs) = partition (isInplaceCompInc c) (componentIncludes c) + hasIdeps' = not $ null ideps + c' = c { componentPackageDeps = error "using deprecated field:componentPackageDeps" + , componentInternalDeps = [] + , componentIncludes = incs } + in (hasIdeps',c') + + needsBuild = needsBuildOutput includeDirs (componentUnitId clbi) + + cleanRecursiveOpts :: Component + -> BuildInfo -> ComponentLocalBuildInfo -> GhcOptions + cleanRecursiveOpts comp libbi libclbi = + let + liboutdir = componentOutDir lbi comp + (_,libclbi') = removeInplace libclbi + (extraIncludes,extraDeps',_ems) = recursiveIncludeDirs includeDirs (componentUnitId libclbi) + (_,extraDeps) = partition (isInplaceCompInc libclbi) extraDeps' + opts = (componentGhcOptions normal lbi libbi libclbi' liboutdir) { + ghcOptPackageDBs = [] + } + + in + opts { ghcOptSourcePath = ghcOptSourcePath opts <> toNubListR extraIncludes + , ghcOptPackages = ghcOptPackages opts <> toNubListR extraDeps } + + libopts = + case (getLibraryClbi pd lbi,getExeClbi pd lbi) of + (Just (lib, libclbi),_) | hasIdeps -> + let + libbi = libBuildInfo lib + opts = cleanRecursiveOpts (CLib lib) libbi libclbi + in + opts { ghcOptInputModules = ghcOptInputModules opts <> (toNubListR $ allLibModules lib libclbi) } + (_,Just (exe,execlbi)) | hasIdeps -> + let + exebi = buildInfo exe + in + cleanRecursiveOpts (CExe exe) exebi execlbi + _ -> mempty + + distDir = fromFlagOrDefault ("." "dist") (configDistPref $ configFlags lbi) + packageDbDir = internalPackageDBPath lbi distDir + (hasIdeps,clbi') = case needsBuild of + NoBuildOutput -> removeInplace clbi + ProduceBuildOutput -> (False, clbi) + libopts' = case needsBuild of + NoBuildOutput -> libopts + ProduceBuildOutput -> mempty { ghcOptPackageDBs = [SpecificPackageDB packageDbDir] } + in (clbi', libopts') +#else +removeInplaceDeps :: Verbosity + -> LocalBuildInfo + -> PackageDescription + -> ComponentLocalBuildInfo + -> (ComponentLocalBuildInfo, GhcOptions) +removeInplaceDeps _v lbi pd clbi = let + (ideps, deps) = partition (isInplaceDep lbi) (componentPackageDeps clbi) + hasIdeps = not $ null ideps + libopts = + case getLibraryClbi pd lbi of + Just (lib, libclbi) | hasIdeps -> + let + libbi = libBuildInfo lib + liboutdir = componentOutDir lbi (CLib lib) + in + (componentGhcOptions normal lbi libbi libclbi liboutdir) { + ghcOptPackageDBs = [] + } + _ -> mempty + clbi' = clbi { componentPackageDeps = deps } + in (clbi', libopts) +#endif + + +#if CH_MIN_VERSION_Cabal(2,0,0) +recursiveDepInfo lbi v distdir = do + includeDirs <- componentsMap lbi v distdir $ \c clbi bi -> do + return (componentUnitId clbi + , ( SubDeps + { sdComponentInternalDeps = componentInternalDeps clbi + , sdHsSourceDirs = hsSourceDirs bi + , sdComponentIncludes = componentIncludes clbi + , sdComponentEntryPoints = componentEntrypoints c}) ) + return $ Map.fromList $ map snd includeDirs + +data SubDeps = SubDeps + { sdComponentInternalDeps :: [UnitId] + , sdHsSourceDirs :: [FilePath] + , sdComponentIncludes :: [(OpenUnitId, ModuleRenaming)] + , sdComponentEntryPoints :: ChEntrypoint + } + +recursiveIncludeDirs :: Map.Map UnitId SubDeps + -> UnitId -> ([FilePath], [(OpenUnitId, ModuleRenaming)] + , ChEntrypoint) +recursiveIncludeDirs includeDirs unit = go ([],[],Nothing) [unit] + where + go (afp,aci,Nothing ) [] = (afp,aci,error "recursiveIncludeDirs:no ChEntrypoint") + go (afp,aci,Just amep) [] = (afp,aci,amep) + go acc@(afp,aci,amep) (u:us) = case Map.lookup u includeDirs of + Nothing -> go acc us + Just (SubDeps us' sfp sci sep) -> go (afp++sfp,aci++sci,Just (combineEp amep sep)) (us++us') + +needsBuildOutput :: Map.Map UnitId SubDeps -> UnitId -> NeedsBuildOutput +needsBuildOutput includeDirs unit = go [unit] + where + isIndef (IndefFullUnitId _ _) = True + isIndef _ = False + go [] = NoBuildOutput + go (u:us) = case Map.lookup u includeDirs of + Nothing -> go us + Just (SubDeps us' sfp sci sep) -> + if any (isIndef . fst) sci + then ProduceBuildOutput + else go (us++us') + +-- | combineEP is used to combine the entrypoints when recursively chasing +-- through the dependencies of a given entry point. The first parameter is the +-- current accumulated value, and the second one is the current sub-dependency +-- being considered. So the bias should be to preserve the type of entrypoint +-- from the first parameter. +combineEp Nothing e = e +combineEp (Just ChSetupEntrypoint) e = e +combineEp (Just (ChLibEntrypoint es1 os1 ss1)) (ChLibEntrypoint es2 os2 ss2) = (ChLibEntrypoint (nub $ es2++es1) (nub $ os2++os1) (nub $ ss2++ss1)) +combineEp _ e@(ChExeEntrypoint mi os2) = error $ "combineEP: cannot have a sub exe:" ++ show e +combineEp (Just (ChExeEntrypoint mi os1)) (ChLibEntrypoint es2 os2 ss2) = (ChExeEntrypoint mi (nub $ os1++es2++os2++ss2)) + +-- no, you unconditionally always wrap the result in Just, so instead of `f x = Just y; f x = Just z` do `f x = y; f x = z` and use f as `Just . f` + + + +instantiatedGhcPackage :: (ModuleName,OpenModule) -> [(OpenUnitId, ModuleRenaming)] +instantiatedGhcPackage (_,OpenModule oui@(DefiniteUnitId _) _) = [(oui,DefaultRenaming)] +instantiatedGhcPackage (_, _) = [] +#endif + +initialBuildStepsForAllComponents distdir pd lbi v = + initialBuildSteps distdir pd lbi v + + + + + + +#if !CH_MIN_VERSION_Cabal(1,25,0) +-- CPP < 1.25 +unFlagName (FlagName n) = n +-- mkFlagName n = FlagName n +#endif + +toDataVersion :: Version -> DataVersion.Version +--fromDataVersion :: DataVersion.Version -> Version +#if CH_MIN_VERSION_Cabal(2,0,0) +toDataVersion v = DataVersion.Version (versionNumbers v) [] +--fromDataVersion (DataVersion.Version vs _) = mkVersion vs +#else +toDataVersion = id +--fromDataVersion = id +#endif + +componentNameToCh _uid CLibName = ChLibName +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 +#if CH_MIN_VERSION_Cabal(2,0,0) +componentNameToCh uid (CSubLibName n) = ChSubLibName uid +#else +componentNameToCh _uid (CSubLibName n) = ChSubLibName (unUnqualComponentName' n) +#endif +componentNameToCh uid (CFLibName n) = ChFLibName (unUnqualComponentName' n) +#endif +componentNameToCh _uid (CExeName n) = ChExeName (unUnqualComponentName' n) +componentNameToCh _uid (CTestName n) = ChTestName (unUnqualComponentName' n) +componentNameToCh _uid (CBenchName n) = ChBenchName (unUnqualComponentName' n) + +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 +unUnqualComponentName' = unUnqualComponentName +#else +unUnqualComponentName' = id +#endif + +#if !CH_MIN_VERSION_Cabal(1,25,0) +-- CPP < 1.25 +componentNameFromComponent (CLib Library {}) = CLibName +#elif CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 (redundant) +componentNameFromComponent (CLib Library { libName = Nothing }) = CLibName +componentNameFromComponent (CLib Library { libName = Just n }) = CSubLibName n +componentNameFromComponent (CFLib ForeignLib {..}) = CFLibName foreignLibName +#endif +componentNameFromComponent (CExe Executable {..}) = CExeName exeName +componentNameFromComponent (CTest TestSuite {..}) = CTestName testName +componentNameFromComponent (CBench Benchmark {..}) = CBenchName benchmarkName + +componentOutDir lbi (CLib Library {..})= + buildDir lbi +#if CH_MIN_VERSION_Cabal(2,0,0) +componentOutDir lbi (CFLib ForeignLib {..}) = + componentOutDir' lbi (unUnqualComponentName foreignLibName) +#endif +componentOutDir lbi (CExe Executable {..}) = + componentOutDir' lbi (unUnqualComponentName' exeName) +componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteExeV10 _ _, ..}) = + componentOutDir' lbi (unUnqualComponentName' testName) +componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteLibV09 _ _, ..}) = + componentOutDir' lbi (unUnqualComponentName' testName ++ "Stub") +componentOutDir lbi (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ _, ..})= + componentOutDir' lbi (unUnqualComponentName' benchmarkName) + +componentOutDir' :: LocalBuildInfo -> String -> FilePath +componentOutDir' lbi compName' = + ----- Copied from Distribution/Simple/GHC.hs:buildOrReplExe + let targetDir = (buildDir lbi) compName' + compDir = targetDir (compName' ++ "-tmp") + in compDir + +componentEntrypoints :: Component -> ChEntrypoint +componentEntrypoints (CLib Library {..}) + = ChLibEntrypoint + (map gmModuleName exposedModules) + (map gmModuleName $ otherModules libBuildInfo) +#if CH_MIN_VERSION_Cabal(2,0,0) + (map gmModuleName signatures) +#else + [] -- no signatures prior to Cabal 2.0 +#endif +#if CH_MIN_VERSION_Cabal(2,0,0) +componentEntrypoints (CFLib (ForeignLib{..})) + = ChLibEntrypoint + [] + (map gmModuleName $ otherModules foreignLibBuildInfo) + [] +#endif +componentEntrypoints (CExe Executable {..}) + = ChExeEntrypoint + modulePath + (map gmModuleName $ otherModules buildInfo) +componentEntrypoints (CTest TestSuite { testInterface = TestSuiteExeV10 _ fp, ..}) + = ChExeEntrypoint fp (map gmModuleName $ otherModules testBuildInfo) +componentEntrypoints (CTest TestSuite { testInterface = TestSuiteLibV09 _ mn, ..}) + = ChLibEntrypoint [gmModuleName mn] (map gmModuleName $ otherModules testBuildInfo) [] +componentEntrypoints (CTest TestSuite {}) + = ChLibEntrypoint [] [] [] +componentEntrypoints (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ fp, ..}) + = ChExeEntrypoint fp (map gmModuleName $ otherModules benchmarkBuildInfo) +componentEntrypoints (CBench Benchmark {}) + = ChLibEntrypoint [] [] [] + +#if CH_MIN_VERSION_Cabal(2,0,0) +isInplaceCompInc :: ComponentLocalBuildInfo -> (OpenUnitId, ModuleRenaming) -> Bool +isInplaceCompInc clbi (DefiniteUnitId uid, _mr) = unDefUnitId uid `elem` componentInternalDeps clbi +isInplaceCompInc clbi (IndefFullUnitId uid _, _mmr) = False +#endif + +#if CH_MIN_VERSION_Cabal(2,0,0) +isInplaceDep :: LocalBuildInfo -> ComponentLocalBuildInfo -> (UnitId, MungedPackageId) -> Bool +isInplaceDep lbi clbi (uid, _mpid) = uid `elem` componentInternalDeps clbi +#else +isInplaceDep :: LocalBuildInfo -> (InstalledPackageId, PackageId) -> Bool +# if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP >= 1.23 +isInplaceDep lbi (ipid, _pid) = localUnitId lbi == ipid +# else +-- CPP <= 1.22 +isInplaceDep _lbi (ipid, pid) = inplacePackageId pid == ipid +# endif +#endif + +#if CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 +-- >= 1.22 uses NubListR +nubPackageFlags opts = opts +#else +nubPackageFlags opts = opts { ghcOptPackages = nub $ ghcOptPackages opts } +#endif + +renderGhcOptions' :: LocalBuildInfo + -> Verbosity + -> GhcOptions + -> IO [String] +#if !CH_MIN_VERSION_Cabal(1,20,0) +renderGhcOptions' lbi v opts = do +-- CPP < 1.20 + (ghcProg, _) <- requireProgram v ghcProgram (withPrograms lbi) + let Just ghcVer = programVersion ghcProg + return $ renderGhcOptions ghcVer opts +#elif CH_MIN_VERSION_Cabal(1,20,0) && !CH_MIN_VERSION_Cabal(1,24,0) +renderGhcOptions' lbi _v opts = do +-- CPP >= 1.20 && < 1.24 + return $ renderGhcOptions (compiler lbi) opts +#else +renderGhcOptions' lbi _v opts = do +-- CPP >= 1.24 + return $ renderGhcOptions (compiler lbi) (hostPlatform lbi) opts +#endif diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Common.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Common.hs new file mode 100644 index 0000000..a7e7377 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Common.hs @@ -0,0 +1,150 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-| +Module : CabalHelper.Shared.Common +Description : Shared utility functions +License : GPL-3 +-} + +{-# LANGUAGE CPP, DeriveDataTypeable, OverloadedStrings #-} +module CabalHelper.Shared.Common where + +#ifdef MIN_VERSION_Cabal +#undef CH_MIN_VERSION_Cabal +#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal +#endif + +import Control.Applicative +import Control.Exception as E +import Control.Monad +import Data.Char +import Data.List +import Data.Maybe +import Data.Version +import Data.Typeable +import Data.ByteString (ByteString) +import qualified Data.ByteString as BS +import qualified Data.ByteString.Char8 as BS8 +#if CH_MIN_VERSION_Cabal(2,2,0) +import qualified Distribution.PackageDescription.Parsec as P +#else +import qualified Distribution.PackageDescription.Parse as P +#endif +import System.Environment +import System.IO +import qualified System.Info +import System.Exit +import System.Directory +import System.FilePath +import Text.ParserCombinators.ReadP +import Prelude + +data Panic = Panic String deriving (Typeable, Show) +instance Exception Panic + +panic :: String -> a +panic msg = throw $ Panic msg + +panicIO :: String -> IO a +panicIO msg = throwIO $ Panic msg + +handlePanic :: IO a -> IO a +handlePanic action = + action `E.catch` \(Panic msg) -> errMsg msg >> exitFailure + +errMsg :: String -> IO () +errMsg str = do + prog <- getProgName + hPutStrLn stderr $ prog ++ ": " ++ str + +-- | @getCabalConfigHeader "dist/setup-config"@ returns the cabal version and +-- compiler version +getCabalConfigHeader :: FilePath -> IO (Maybe (Version, (ByteString, Version))) +getCabalConfigHeader file = bracket (openFile file ReadMode) hClose $ \h -> do + parseHeader <$> BS.hGetLine h + +parseHeader :: ByteString -> Maybe (Version, (ByteString, Version)) +parseHeader header = case BS8.words header of + ["Saved", "package", "config", "for", _pkgId , + "written", "by", cabalId, + "using", compId] + -> liftM2 (,) (snd <$> parsePkgId cabalId) (parsePkgId compId) + _ -> Nothing + +parsePkgId :: ByteString -> Maybe (ByteString, Version) +parsePkgId bs = + case BS8.split '-' bs of + [pkg, vers] -> Just (pkg, parseVer $ BS8.unpack vers) + _ -> Nothing + +parseVer :: String -> Version +parseVer vers = runReadP parseVersion vers + +trim :: String -> String +trim = dropWhileEnd isSpace + +majorVer :: Version -> Version +majorVer (Version b _) = Version (take 2 b) [] + +sameMajorVersionAs :: Version -> Version -> Bool +sameMajorVersionAs a b = majorVer a == majorVer b + +runReadP :: ReadP t -> String -> t +runReadP p i = case filter ((=="") . snd) $ readP_to_S p i of + (a,""):[] -> a + _ -> error $ "Error parsing: " ++ show i + +appCacheDir :: IO FilePath +appCacheDir = + ( "cabal-helper") <$> getEnvDefault "XDG_CACHE_HOME" (homeRel cache) + where + -- for GHC 7.4 + lookupEnv' var = do env <- getEnvironment; return (lookup var env) + getEnvDefault var def = lookupEnv' var >>= \m -> case m of Nothing -> def; Just x -> return x + homeRel path = ( path) <$> getHomeDirectory + cache = + case System.Info.os of + "mingw32" -> windowsCache + _ -> unixCache + + windowsCache = "Local Settings" "Cache" + unixCache = ".cache" + +isCabalFile :: FilePath -> Bool +isCabalFile f = takeExtension' f == ".cabal" + +takeExtension' :: FilePath -> String +takeExtension' p = + if takeFileName p == takeExtension p + then "" -- just ".cabal" is not a valid cabal file + else takeExtension p + +replace :: String -> String -> String -> String +replace n r hs' = go "" hs' + where + go acc h + | take (length n) h == n = + reverse acc ++ r ++ drop (length n) h + go acc (h:hs) = go (h:acc) hs + go acc [] = reverse acc + + +#if CH_MIN_VERSION_Cabal(2,2,0) +readPackageDescription = P.readGenericPackageDescription +#else +readPackageDescription = P.readPackageDescription +#endif diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/InterfaceTypes.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/InterfaceTypes.hs new file mode 100644 index 0000000..a108c72 --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/InterfaceTypes.hs @@ -0,0 +1,81 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2018 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DefaultSignatures #-} + +{-| +Module : CabalHelper.Shared.InterfaceTypes +Description : Types which are used by c-h library and executable to communicate +License : GPL-3 + +These types are used to communicate between the cabal-helper library and main +executable, using Show/Read. If any types in this module change the major +version must be bumped since this will be exposed in the @Distribution.Helper@ +module. + +The cached executables in @$XDG_CACHE_HOME/cabal-helper@ use the cabal-helper +version (among other things) as a cache key so we don't need to worry about +talking to an old executable. +-} +module CabalHelper.Shared.InterfaceTypes where + +import GHC.Generics +import Data.Version + +data ChResponse + = ChResponseCompList [(ChComponentName, [String])] + | ChResponseEntrypoints [(ChComponentName, ChEntrypoint)] + | ChResponseNeedsBuild [(ChComponentName, NeedsBuildOutput)] + | ChResponseList [String] + | ChResponsePkgDbs [ChPkgDb] + | ChResponseLbi String + | ChResponseVersion String Version + | ChResponseLicenses [(String, [(String, Version)])] + | ChResponseFlags [(String, Bool)] + deriving (Eq, Ord, Read, Show, Generic) + +data ChComponentName = ChSetupHsName + | ChLibName + | ChSubLibName String + | ChFLibName String + | ChExeName String + | ChTestName String + | ChBenchName String + deriving (Eq, Ord, Read, Show, Generic) + +newtype ChModuleName = ChModuleName String + deriving (Eq, Ord, Read, Show, Generic) + +data ChEntrypoint = ChSetupEntrypoint -- ^ Almost like 'ChExeEntrypoint' but + -- @main-is@ could either be @"Setup.hs"@ + -- or @"Setup.lhs"@. Since we don't know + -- where the source directory is you have + -- to find these files. + | ChLibEntrypoint { chExposedModules :: [ChModuleName] + , chOtherModules :: [ChModuleName] + , chSignatures :: [ChModuleName] -- backpack only + } + | ChExeEntrypoint { chMainIs :: FilePath + , chOtherModules :: [ChModuleName] + } deriving (Eq, Ord, Read, Show, Generic) + +data ChPkgDb = ChPkgGlobal + | ChPkgUser + | ChPkgSpecific FilePath + deriving (Eq, Ord, Read, Show, Generic) + +data NeedsBuildOutput = ProduceBuildOutput | NoBuildOutput + deriving (Eq, Ord, Read, Show, Generic) diff --git a/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Sandbox.hs b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Sandbox.hs new file mode 100644 index 0000000..2f3774f --- /dev/null +++ b/vendor/cabal-helper-0.8.1.2/src/CabalHelper/Shared/Sandbox.hs @@ -0,0 +1,78 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015-2017 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . + +{-| +Module : CabalHelper.Shared.Sandbox +Description : Extracting information from @cabal.sandbox.config@ files +License : GPL-3 +-} + +module CabalHelper.Shared.Sandbox where + +import Control.Applicative +import Data.Char +import Data.Maybe +import Data.List +import Data.Version +import System.FilePath +import System.Directory +import Prelude + +import qualified Data.Traversable as T + +-- | Get the path to the sandbox package-db in a project +getSandboxPkgDb :: FilePath + -- ^ Path to the cabal package root directory (containing the + -- @cabal.sandbox.config@ file) + -> String + -- ^ Cabal build platform, i.e. @buildPlatform@ + -> Version + -- ^ GHC version (@cProjectVersion@ is your friend) + -> IO (Maybe FilePath) +getSandboxPkgDb d platform ghcVer = do + mConf <- T.traverse readFile =<< mightExist (d "cabal.sandbox.config") + return $ fixPkgDbVer <$> (extractSandboxDbDir =<< mConf) + + where + fixPkgDbVer dir = + case takeFileName dir == ghcSandboxPkgDbDir platform ghcVer of + True -> dir + False -> takeDirectory dir ghcSandboxPkgDbDir platform ghcVer + +ghcSandboxPkgDbDir :: String -> Version -> String +ghcSandboxPkgDbDir platform ghcVer = + platform ++ "-ghc-" ++ showVersion ghcVer ++ "-packages.conf.d" + +-- | Extract the sandbox package db directory from the cabal.sandbox.config +-- file. Exception is thrown if the sandbox config file is broken. +extractSandboxDbDir :: String -> Maybe FilePath +extractSandboxDbDir conf = extractValue <$> parse conf + where + key = "package-db:" + keyLen = length key + + parse = listToMaybe . filter (key `isPrefixOf`) . lines + extractValue = CabalHelper.Shared.Sandbox.dropWhileEnd isSpace . dropWhile isSpace . drop keyLen + + +mightExist :: FilePath -> IO (Maybe FilePath) +mightExist f = do + exists <- doesFileExist f + return $ if exists then (Just f) else (Nothing) + +-- dropWhileEnd is not provided prior to base 4.5.0.0. +dropWhileEnd :: (a -> Bool) -> [a] -> [a] +dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) [] -- cgit v1.2.3