From 4b7b646c4fddb1c368aead0315a1f6ce0784b230 Mon Sep 17 00:00:00 2001 From: Daniel Gröber Date: Thu, 28 Sep 2017 21:33:24 +0200 Subject: Move split source into src/ and lib/ --- CabalHelper/Compiletime/Compat/Environment.hs | 6 - CabalHelper/Compiletime/Compat/Version.hs | 25 - CabalHelper/Compiletime/Compile.hs | 595 ---------------------- CabalHelper/Compiletime/Data.hs | 86 ---- CabalHelper/Compiletime/GuessGhc.hs | 92 ---- CabalHelper/Compiletime/Log.hs | 44 -- CabalHelper/Compiletime/Types.hs | 40 -- CabalHelper/Compiletime/Wrapper.hs | 164 ------ CabalHelper/Runtime/Licenses.hs | 125 ----- CabalHelper/Runtime/Main.hs | 539 -------------------- CabalHelper/Shared/Common.hs | 128 ----- CabalHelper/Shared/InterfaceTypes.hs | 75 --- CabalHelper/Shared/Sandbox.hs | 77 --- Distribution/Helper.hs | 527 ------------------- cabal-helper.cabal | 9 +- lib/Distribution/Helper.hs | 527 +++++++++++++++++++ src/CabalHelper/Compiletime/Compat/Environment.hs | 6 + src/CabalHelper/Compiletime/Compat/Version.hs | 25 + src/CabalHelper/Compiletime/Compile.hs | 595 ++++++++++++++++++++++ src/CabalHelper/Compiletime/Data.hs | 86 ++++ src/CabalHelper/Compiletime/GuessGhc.hs | 92 ++++ src/CabalHelper/Compiletime/Log.hs | 44 ++ src/CabalHelper/Compiletime/Types.hs | 40 ++ src/CabalHelper/Compiletime/Wrapper.hs | 164 ++++++ src/CabalHelper/Runtime/Licenses.hs | 125 +++++ src/CabalHelper/Runtime/Main.hs | 539 ++++++++++++++++++++ src/CabalHelper/Shared/Common.hs | 128 +++++ src/CabalHelper/Shared/InterfaceTypes.hs | 75 +++ src/CabalHelper/Shared/Sandbox.hs | 77 +++ 29 files changed, 2529 insertions(+), 2526 deletions(-) delete mode 100644 CabalHelper/Compiletime/Compat/Environment.hs delete mode 100644 CabalHelper/Compiletime/Compat/Version.hs delete mode 100644 CabalHelper/Compiletime/Compile.hs delete mode 100644 CabalHelper/Compiletime/Data.hs delete mode 100644 CabalHelper/Compiletime/GuessGhc.hs delete mode 100644 CabalHelper/Compiletime/Log.hs delete mode 100644 CabalHelper/Compiletime/Types.hs delete mode 100644 CabalHelper/Compiletime/Wrapper.hs delete mode 100644 CabalHelper/Runtime/Licenses.hs delete mode 100644 CabalHelper/Runtime/Main.hs delete mode 100644 CabalHelper/Shared/Common.hs delete mode 100644 CabalHelper/Shared/InterfaceTypes.hs delete mode 100644 CabalHelper/Shared/Sandbox.hs delete mode 100644 Distribution/Helper.hs create mode 100644 lib/Distribution/Helper.hs create mode 100644 src/CabalHelper/Compiletime/Compat/Environment.hs create mode 100644 src/CabalHelper/Compiletime/Compat/Version.hs create mode 100644 src/CabalHelper/Compiletime/Compile.hs create mode 100644 src/CabalHelper/Compiletime/Data.hs create mode 100644 src/CabalHelper/Compiletime/GuessGhc.hs create mode 100644 src/CabalHelper/Compiletime/Log.hs create mode 100644 src/CabalHelper/Compiletime/Types.hs create mode 100644 src/CabalHelper/Compiletime/Wrapper.hs create mode 100644 src/CabalHelper/Runtime/Licenses.hs create mode 100644 src/CabalHelper/Runtime/Main.hs create mode 100644 src/CabalHelper/Shared/Common.hs create mode 100644 src/CabalHelper/Shared/InterfaceTypes.hs create mode 100644 src/CabalHelper/Shared/Sandbox.hs diff --git a/CabalHelper/Compiletime/Compat/Environment.hs b/CabalHelper/Compiletime/Compat/Environment.hs deleted file mode 100644 index 916f782..0000000 --- a/CabalHelper/Compiletime/Compat/Environment.hs +++ /dev/null @@ -1,6 +0,0 @@ -module CabalHelper.Compiletime.Compat.Environment where - -import System.Environment - -lookupEnv :: String -> IO (Maybe String) -lookupEnv var = do env <- getEnvironment; return (lookup var env) diff --git a/CabalHelper/Compiletime/Compat/Version.hs b/CabalHelper/Compiletime/Compat/Version.hs deleted file mode 100644 index 853aca5..0000000 --- a/CabalHelper/Compiletime/Compat/Version.hs +++ /dev/null @@ -1,25 +0,0 @@ -{-# LANGUAGE CPP #-} -module CabalHelper.Compiletime.Compat.Version - ( DataVersion - , toDataVersion - , fromDataVersion - , Data.Version.showVersion - ) 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 diff --git a/CabalHelper/Compiletime/Compile.hs b/CabalHelper/Compiletime/Compile.hs deleted file mode 100644 index 8cc565e..0000000 --- a/CabalHelper/Compiletime/Compile.hs +++ /dev/null @@ -1,595 +0,0 @@ --- 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 Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . -{-# LANGUAGE RecordWildCards, FlexibleContexts #-} - -{-| -Module : CabalHelper.Compiletime.Compile -Description : Runtime compilation machinery -License : AGPL-3 --} - -module CabalHelper.Compiletime.Compile where - -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.Traversable -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 System.Directory -import System.FilePath -import System.Process -import System.Exit -import System.IO -import System.IO.Error -import System.IO.Temp -import Prelude - -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 = Compile { - compCabalSourceDir :: Maybe CabalSourceDir, - compPackageDb :: Maybe PackageDbDir, - compCabalVersion :: Either String Version, - compPackageDeps :: [String] - } - -compileHelper :: Options -> Version -> FilePath -> FilePath -> IO (Either ExitCode FilePath) -compileHelper opts cabalVer projdir distdir = do - case cabalPkgDb opts of - Nothing -> - run [ compileCabalSource - , Right <$> MaybeT (cachedExe cabalVer) - , compileSandbox - , compileGlobal - , cachedCabalPkg - , MaybeT (Just <$> compilePrivatePkgDb) - ] - mdb -> - run [ Right <$> MaybeT (cachedExe cabalVer) - , liftIO $ compileWithPkg mdb cabalVer - ] - - where - run actions = fromJust <$> runMaybeT (msum actions) - - logMsg = "compiling helper with Cabal from " - --- for relaxed deps: find (sameMajorVersionAs cabalVer) . reverse . sort - - -- | Check if this version is globally available - compileGlobal :: MaybeT IO (Either ExitCode FilePath) - compileGlobal = do - ver <- MaybeT $ find (== cabalVer) <$> listCabalVersions opts - vLog opts $ logMsg ++ "user/global package-db" - liftIO $ compileWithPkg Nothing ver - - -- | Check if this version is available in the project sandbox - compileSandbox :: MaybeT IO (Either ExitCode FilePath) - compileSandbox = do - let ghcVer = ghcVersion opts - mdb_path = getSandboxPkgDb projdir (display buildPlatform) =<< ghcVer - sandbox <- PackageDbDir <$> MaybeT mdb_path - ver <- MaybeT $ logIOError opts "compileSandbox" $ - find (== cabalVer) <$> listCabalVersions' opts (Just sandbox) - vLog opts $ logMsg ++ "sandbox package-db" - liftIO $ compileWithPkg (Just sandbox) ver - - - -- | Check if we already compiled this version of cabal into a private - -- package-db - cachedCabalPkg :: MaybeT IO (Either ExitCode FilePath) - cachedCabalPkg = do - db_exists <- liftIO $ cabalVersionExistsInPkgDb opts cabalVer - case db_exists of - False -> mzero - True -> do - db@(PackageDbDir db_path) - <- liftIO $ getPrivateCabalPkgDb opts (Right cabalVer) - vLog opts $ logMsg ++ "private package-db in " ++ db_path - liftIO $ compileWithPkg (Just db) cabalVer - - -- | See if we're in a cabal source tree - compileCabalSource :: MaybeT IO (Either ExitCode FilePath) - compileCabalSource = do - let cabalFile = projdir "Cabal.cabal" - cabalSrc <- liftIO $ doesFileExist cabalFile - let projdir' = CabalSourceDir projdir - case cabalSrc of - False -> mzero - True -> liftIO $ do - vLog opts $ "directory above distdir looks like cabal source tree (Cabal.cabal exists)" - ver <- cabalFileVersion <$> readFile cabalFile - vLog opts $ "compiling helper with local Cabal source tree" - compileWithCabalTree ver projdir' - - -- | Compile the requested cabal version into an isolated package-db - compilePrivatePkgDb :: IO (Either ExitCode FilePath) - compilePrivatePkgDb = do - db <- fst <$> installCabal opts (Right cabalVer) `E.catch` - \(SomeException _) -> errorInstallCabal cabalVer distdir - compileWithPkg (Just db) cabalVer - - compileWithCabalTree ver srcDir = - compile distdir opts $ Compile { - compCabalSourceDir = Just srcDir, - compPackageDb = Nothing, - compCabalVersion = Right ver, - compPackageDeps = [] - } - - compileWithPkg mdb ver = - compile distdir opts $ Compile { - compCabalSourceDir = Nothing, - compPackageDb = mdb, - compCabalVersion = Right ver, - compPackageDeps = [cabalPkgId ver] - } - - cabalPkgId v = "Cabal-" ++ showVersion v - -compile :: FilePath -> Options -> Compile -> IO (Either ExitCode FilePath) -compile distdir opts@Options {..} Compile {..} = do - cnCabalSourceDir - <- (canonicalizePath . cabalSourceDir) `traverse` compCabalSourceDir - appdir <- appCacheDir - - let (outdir, exedir, exe, mchsrcdir) = - case cnCabalSourceDir of - Nothing -> ( exeName compCabalVersion <.> "build" - , appdir - , appdir exeName compCabalVersion - , Nothing - ) - Just _ -> ( distdir "cabal-helper" - , distdir - , distdir "cabal-helper" "cabal-helper" - , Just $ distdir "cabal-helper" - ) - - createDirectoryIfMissing True outdir - createDirectoryIfMissing True exedir - - withHelperSources mchsrcdir $ \compCabalHelperSourceDir -> do - - vLog opts $ "sourcedir: " ++ compCabalHelperSourceDir - vLog opts $ "outdir: " ++ outdir - vLog opts $ "exe: " ++ exe - - let (mj1:mj2:mi:_) = case compCabalVersion of - Left _commitid -> [10000000, 0, 0] - Right (Version vs _) -> vs - let ghc_opts = concat [ - [ "-outputdir", outdir - , "-o", exe - , "-optP-DCABAL_HELPER=1" - , "-optP-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++")" - ], - maybeToList $ ("-package-conf="++) <$> packageDbDir <$> compPackageDb, - map ("-i"++) $ nub $ "":compCabalHelperSourceDir:maybeToList cnCabalSourceDir, - - if isNothing cnCabalSourceDir - then [ "-hide-all-packages" - , "-package", "base" - , "-package", "containers" - , "-package", "directory" - , "-package", "filepath" - , "-package", "process" - , "-package", "bytestring" - , "-package", "ghc-prim" - ] - else [], - - concatMap (\p -> ["-package", p]) compPackageDeps, - [ "--make" - , compCabalHelperSourceDir"CabalHelper""Runtime""Main.hs" - ] - ] - - rv <- callProcessStderr' opts Nothing ghcProgram ghc_opts - return $ case rv of - ExitSuccess -> Right exe - e@(ExitFailure _) -> Left e - -exeName :: Either String Version -> String -exeName (Left commitid) = intercalate "-" - [ "cabal-helper" ++ showVersion version -- our ver - , "CabalHEAD" ++ commitid - ] -exeName (Right compCabalVersion) = intercalate "-" - [ "cabal-helper" ++ showVersion version -- our ver - , "Cabal" ++ showVersion compCabalVersion - ] - -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, Either String Version) -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, e_commit_ver) <- case ever of - Left HEAD -> do - second Left <$> unpackCabalHEAD tmpdir - Right ver -> do - message ver - let patch = fromMaybe nopCabalPatchDescription $ - find ((ver`elem`) . cpdVersions) patchyCabalVersions - (,) <$> unpackPatchedCabal opts ver tmpdir patch <*> pure (Right ver) - - db <- createPkgDb opts e_commit_ver - - runCabalInstall opts db srcdir ever - - return (db, e_commit_ver) - -{- -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 - cabalInstallVer <- cabalInstallVersion opts - cabal_opts <- return $ concat - [ - [ "--package-db=clear" - , "--package-db=global" - , "--package-db=" ++ db - , "--prefix=" ++ db "prefix" - ] - , cabalOptions opts - , if cabalInstallVer >= Version [1,20,0,0] [] - then ["--no-require-sandbox"] - else [] - , [ "install", srcdir ] - , if verbose opts - then ["-v"] - else [] - , [ "--only-dependencies" ] - ] - - callProcessStderr opts (Just "/") (cabalProgram opts) cabal_opts - - setupProgram <- compileSetupHs opts db srcdir - runSetupHs opts setupProgram db srcdir ever - - hPutStrLn stderr "done" - -cabalOptions :: Options -> [String] -cabalOptions opts = - concat [ [ "--with-ghc=" ++ ghcProgram opts ] - , if ghcPkgProgram opts /= ghcPkgProgram defaultOptions - then [ "--with-ghc-pkg=" ++ ghcPkgProgram opts ] - else [] - ] - -runSetupHs - :: Options - -> SetupProgram - -> FilePath - -> FilePath - -> Either HEAD Version - -> IO () -runSetupHs opts SetupProgram {..} db srcdir ever = do - let run = callProcessStderr opts (Just srcdir) setupProgram - parmake_opt - | Right ver <- ever, ver >= Version [1,20] [] = ["-j"] - | otherwise = [] - - run $ [ "configure", "--package-db", db, "--prefix", db "prefix" ] ++ cabalOptions opts - run $ [ "build" ] ++ parmake_opt - 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) (ghcProgram 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 { cabalSourceDir :: 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) (cabalProgram opts) args - return $ CabalSourceDir dir - -unpackCabalHEAD :: FilePath -> IO (CabalSourceDir, String) -unpackCabalHEAD 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 "git" ["rev-parse", "HEAD"] "" - return (CabalSourceDir $ dir "Cabal", 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 - -cachedExe :: Version -> IO (Maybe FilePath) -cachedExe compCabalVersion = do - appdir <- appCacheDir - let exe = appdir exeName (Right compCabalVersion) - exists <- doesFileExist exe - return $ if exists then Just exe else Nothing - -listCabalVersions :: Options -> IO [Version] -listCabalVersions opts = listCabalVersions' opts Nothing - --- TODO: Include sandbox? Probably only relevant for build-type:custom projects. -listCabalVersions' :: Options -> Maybe PackageDbDir -> IO [Version] -listCabalVersions' Options {..} mdb = do - let mdbopt = ("--package-conf="++) <$> packageDbDir <$> mdb - opts = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt - - catMaybes . map (fmap snd . parsePkgId . fromString) . words - <$> readProcess ghcPkgProgram opts "" - -cabalVersionExistsInPkgDb :: Options -> Version -> IO Bool -cabalVersionExistsInPkgDb opts cabalVer = do - db@(PackageDbDir db_path) <- getPrivateCabalPkgDb opts (Right cabalVer) - exists <- doesDirectoryExist db_path - case exists of - False -> return False - True -> do - vers <- listCabalVersions' opts (Just db) - return $ cabalVer `elem` vers - - -ghcVersion :: Options -> IO Version -ghcVersion Options {..} = do - parseVer . trim <$> readProcess ghcProgram ["--numeric-version"] "" - -ghcPkgVersion :: Options -> IO Version -ghcPkgVersion Options {..} = do - parseVer . trim . dropWhile (not . isDigit) <$> readProcess ghcPkgProgram ["--version"] "" - -cabalInstallVersion :: Options -> IO Version -cabalInstallVersion Options {..} = do - parseVer . trim <$> readProcess cabalProgram ["--numeric-version"] "" - -trim :: String -> String -trim = dropWhileEnd isSpace - -createPkgDb :: Options -> Either String Version -> IO PackageDbDir -createPkgDb opts@Options {..} cabalVer = do - db@(PackageDbDir db_path) <- getPrivateCabalPkgDb opts cabalVer - exists <- doesDirectoryExist db_path - when (not exists) $ callProcessStderr opts Nothing ghcPkgProgram ["init", db_path] - return db - -getPrivateCabalPkgDb :: Options -> Either String Version -> 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 cabalFile = - fromJust $ parseVer . extract <$> find ("version:" `isPrefixOf`) ls - where - ls = map (map toLower) $ lines cabalFile - extract = dropWhile (/=':') >>> drop 1 >>> dropWhile isSpace >>> takeWhile (not . isSpace) diff --git a/CabalHelper/Compiletime/Data.hs b/CabalHelper/Compiletime/Data.hs deleted file mode 100644 index 2842cfc..0000000 --- a/CabalHelper/Compiletime/Data.hs +++ /dev/null @@ -1,86 +0,0 @@ --- 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 Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero 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 : AGPL-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.Posix.Files -import System.Posix.Time -import System.Posix.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 - -withHelperSources :: Maybe FilePath -> (FilePath -> IO a) -> IO a -withHelperSources mdir action = withDir mdir $ \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 - - action dir - where - withDir (Just dir) = \f -> f dir - withDir Nothing = withSystemTempDirectoryEnv "cabal-helper-source" - - -sourceFiles :: [(FilePath, String)] -sourceFiles = - [ ("Runtime/Main.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Runtime/Main.hs"))) - , ("Runtime/Licenses.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Runtime/Licenses.hs"))) - , ("Shared/Common.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Shared/Common.hs"))) - , ("Shared/Sandbox.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Shared/Sandbox.hs"))) - , ("Shared/InterfaceTypes.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Shared/InterfaceTypes.hs"))) - ] diff --git a/CabalHelper/Compiletime/GuessGhc.hs b/CabalHelper/Compiletime/GuessGhc.hs deleted file mode 100644 index f4b33d5..0000000 --- a/CabalHelper/Compiletime/GuessGhc.hs +++ /dev/null @@ -1,92 +0,0 @@ --- Copyright (c) 2003-2014, Isaac Jones, Simon Marlow, Martin Sjögren, --- Bjorn Bringert, Krasimir Angelov, --- Malcolm Wallace, Ross Patterson, Ian Lynagh, --- Duncan Coutts, Thomas Schilling, --- Johan Tibell, Mikhail Glushenkov --- All rights reserved. - --- Redistribution and use in source and binary forms, with or without --- modification, are permitted provided that the following conditions are --- met: - --- * Redistributions of source code must retain the above copyright --- notice, this list of conditions and the following disclaimer. - --- * Redistributions in binary form must reproduce the above --- copyright notice, this list of conditions and the following --- disclaimer in the documentation and/or other materials provided --- with the distribution. - --- * Neither the name of Isaac Jones nor the names of other --- contributors may be used to endorse or promote products derived --- from this software without specific prior written permission. - --- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --- OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. - -{-| -Module : CabalHelper.Compiletime.GuessGhc -Description : Logic for finding @ghc-pkg@ based on path to @ghc@ -License : BSD3 --} - -module CabalHelper.Compiletime.GuessGhc (guessToolFromGhcPath) where - -import Data.Maybe -import Data.Char -import Distribution.Simple.BuildPaths -import System.Directory -import System.FilePath - -guessToolFromGhcPath :: FilePath -- ^ Tool name - -> FilePath -- ^ GHC exe path - -> IO (Maybe FilePath) -guessToolFromGhcPath toolname ghcPath - = do let - path = ghcPath - dir = takeDirectory path - versionSuffix = takeVersionSuffix (dropExeExtension path) - guessNormal = dir toolname <.> exeExtension' - guessGhcVersioned = dir (toolname ++ "-ghc" ++ versionSuffix) - <.> exeExtension' - guessVersioned = dir (toolname ++ versionSuffix) - <.> exeExtension' - guesses | null versionSuffix = [guessNormal] - | otherwise = [guessGhcVersioned, - guessVersioned, - guessNormal] - exists <- mapM doesFileExist guesses - return $ listToMaybe [ file | (file, True) <- zip guesses exists ] - - where takeVersionSuffix :: FilePath -> String - takeVersionSuffix = takeWhileEndLE isSuffixChar - - isSuffixChar :: Char -> Bool - isSuffixChar c = isDigit c || c == '.' || c == '-' - - dropExeExtension :: FilePath -> FilePath - dropExeExtension filepath = - case splitExtension filepath of - (filepath', extension) | extension == exeExtension' -> filepath' - | otherwise -> filepath - --- | @takeWhileEndLE p@ is equivalent to @reverse . takeWhile p . reverse@, but --- is usually faster (as well as being easier to read). -takeWhileEndLE :: (a -> Bool) -> [a] -> [a] -takeWhileEndLE p = fst . foldr go ([], False) - where - go x (rest, done) - | not done && p x = (x:rest, False) - | otherwise = (rest, True) - -exeExtension' :: FilePath -exeExtension' = Distribution.Simple.BuildPaths.exeExtension diff --git a/CabalHelper/Compiletime/Log.hs b/CabalHelper/Compiletime/Log.hs deleted file mode 100644 index a75f8b7..0000000 --- a/CabalHelper/Compiletime/Log.hs +++ /dev/null @@ -1,44 +0,0 @@ --- 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 Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-# LANGUAGE ScopedTypeVariables #-} - -{-| -Module : CabalHelper.Compiletime.Log -Description : Basic logging facilities -License : AGPL-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 { verbose = 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/CabalHelper/Compiletime/Types.hs b/CabalHelper/Compiletime/Types.hs deleted file mode 100644 index bfe9b7c..0000000 --- a/CabalHelper/Compiletime/Types.hs +++ /dev/null @@ -1,40 +0,0 @@ --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DefaultSignatures #-} - -{-| -Module : CabalHelper.Compiletime.Types -Description : Types used throughout -License : AGPL-3 --} - -module CabalHelper.Compiletime.Types where - -import Data.Version - -data Options = Options { - verbose :: Bool - , ghcProgram :: FilePath - , ghcPkgProgram :: FilePath - , cabalProgram :: FilePath - , cabalVersion :: Maybe Version - , cabalPkgDb :: Maybe PackageDbDir -} - -newtype PackageDbDir = PackageDbDir { packageDbDir :: FilePath } - -defaultOptions :: Options -defaultOptions = Options False "ghc" "ghc-pkg" "cabal" Nothing Nothing diff --git a/CabalHelper/Compiletime/Wrapper.hs b/CabalHelper/Compiletime/Wrapper.hs deleted file mode 100644 index 6713944..0000000 --- a/CabalHelper/Compiletime/Wrapper.hs +++ /dev/null @@ -1,164 +0,0 @@ --- cabal-helper: Simple interface to Cabal's configuration state --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . -{-# LANGUAGE RecordWildCards, FlexibleContexts #-} -module Main where - -import Control.Applicative -import Control.Monad -import Data.Char -import Data.List -import Data.Maybe -import Data.String -import Text.Printf -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 Distribution.System (buildPlatform) -import Distribution.Text (display) -import Distribution.Verbosity (silent, deafening) -import Distribution.PackageDescription.Parse (readPackageDescription) -import Distribution.Package (packageName, packageVersion) - -import Paths_cabal_helper (version) -import CabalHelper.Compiletime.Compat.Version -import CabalHelper.Compiletime.Compile -import CabalHelper.Compiletime.GuessGhc -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\ -\ PROJ_DIR DIST_DIR ( print-exe | package-id | [CABAL_HELPER_ARGS...] ) )\n" - -globalArgSpec :: [OptDescr (Options -> Options)] -globalArgSpec = - [ option "" ["verbose"] "Be more verbose" $ - NoArg $ \o -> o { verbose = True } - - , option "" ["with-ghc"] "GHC executable to use" $ - reqArg "PROG" $ \p o -> o { ghcProgram = p } - - , option "" ["with-ghc-pkg"] "ghc-pkg executable to use (only needed when guessing from GHC path fails)" $ - reqArg "PROG" $ \p o -> o { ghcPkgProgram = p } - - , option "" ["with-cabal"] "cabal-install executable to use" $ - reqArg "PROG" $ \p o -> o { cabalProgram = p } - - , option "" ["with-cabal-version"] "Cabal library version to use" $ - reqArg "VERSION" $ \p o -> o { cabalVersion = Just $ parseVer p } - - , option "" ["with-cabal-pkg-db"] "package database to look for Cabal library in" $ - reqArg "PKG_DB" $ \p o -> o { cabalPkgDb = 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 - if not (same ghcProgram opts dopts) && same ghcPkgProgram opts dopts - then do - mghcPkg <- guessToolFromGhcPath "ghc-pkg" (ghcProgram opts) - return opts { - ghcPkgProgram = fromMaybe (ghcPkgProgram opts) mghcPkg - } - else return opts - 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 { verbose = True } - Nothing -> opts - -main :: IO () -main = handlePanic $ do - (opts', args) <- parseCommandArgs defaultOptions <$> getArgs - opts <- overrideVerbosityEnvVar =<< guessProgramPaths opts' - case args of - [] -> 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 | verbose 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)] - - projdir:distdir:args' -> do - cfgf <- canonicalizePath (distdir "setup-config") - mhdr <- getCabalConfigHeader cfgf - case mhdr 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, _) -> do - case cabalVersion opts of - Just ver | hdrCabalVersion /= ver -> panic $ printf "\ -\Cabal version %s was requested but setup configuration was\n\ -\written by version %s" (showVersion ver) (showVersion hdrCabalVersion) - _ -> do - eexe <- compileHelper opts hdrCabalVersion projdir distdir - case eexe of - Left e -> exitWith e - Right exe -> - case args' of - "print-exe":_ -> putStrLn exe - _ -> do - (_,_,_,h) <- createProcess $ proc exe args - exitWith =<< waitForProcess h - _ -> error "invalid command line" diff --git a/CabalHelper/Runtime/Licenses.hs b/CabalHelper/Runtime/Licenses.hs deleted file mode 100644 index a1794ea..0000000 --- a/CabalHelper/Runtime/Licenses.hs +++ /dev/null @@ -1,125 +0,0 @@ -{-# LANGUAGE CPP #-} - -#ifdef MIN_VERSION_Cabal -#undef CH_MIN_VERSION_Cabal -#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal -#endif - -module CabalHelper.Runtime.Licenses ( - displayDependencyLicenseList - , groupByLicense - , getDependencyInstalledPackageInfos - ) where - --- Copyright (c) 2014, Jasper Van der Jeugt - --------------------------------------------------------------------------------- -import Control.Arrow ((***), (&&&)) -import Control.Monad (forM_, unless) -import Data.List (foldl', sort) -import Data.Maybe (catMaybes) -import Data.Set (Set) -import qualified Data.Set as Set -import System.Directory (getDirectoryContents) -import System.Exit (exitFailure) -import System.FilePath (takeExtension) -import System.IO (hPutStrLn, stderr) - -import Distribution.InstalledPackageInfo -import Distribution.License -import Distribution.Package -import Distribution.Simple.Configure -import Distribution.Simple.LocalBuildInfo -import Distribution.Simple.PackageIndex -import Distribution.Text -import Distribution.ModuleName -import Distribution.Version (Version) --------------------------------------------------------------------------------- - - - -#if CH_MIN_VERSION_Cabal(1,23,0) --- CPP > 1.22 -type CPackageIndex a = PackageIndex (InstalledPackageInfo) -#elif CH_MIN_VERSION_Cabal(1,22,0) --- CPP >= 1.22 -type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a) -#else -type CPackageIndex a = PackageIndex -#endif - -#if CH_MIN_VERSION_Cabal(1,23,0) --- CPP >= 1.23 -type CInstalledPackageId = UnitId -lookupInstalledPackageId' :: PackageIndex a -> UnitId -> Maybe a -lookupInstalledPackageId' = lookupUnitId -#else -type CInstalledPackageId = InstalledPackageId -lookupInstalledPackageId' = lookupInstalledPackageId -#endif - -findTransitiveDependencies - :: CPackageIndex Distribution.ModuleName.ModuleName - -> Set CInstalledPackageId - -> Set CInstalledPackageId -findTransitiveDependencies pkgIdx set0 = go Set.empty (Set.toList set0) - where - go set [] = set - go set (q : queue) - | q `Set.member` set = go set queue - | otherwise = - case lookupInstalledPackageId' pkgIdx q of - Nothing -> - -- Not found can mean that the package still needs to be - -- installed (e.g. a component of the target cabal package). - -- We can ignore those. - go set queue - Just ipi -> - go (Set.insert q set) (Distribution.InstalledPackageInfo.depends ipi ++ queue) - - --------------------------------------------------------------------------------- -getDependencyInstalledPackageIds - :: LocalBuildInfo -> Set CInstalledPackageId -getDependencyInstalledPackageIds lbi = - findTransitiveDependencies (installedPkgs lbi) $ - Set.fromList $ map fst $ externalPackageDeps lbi - --------------------------------------------------------------------------------- -getDependencyInstalledPackageInfos - :: LocalBuildInfo -> [InstalledPackageInfo] -getDependencyInstalledPackageInfos lbi = catMaybes $ - map (lookupInstalledPackageId' pkgIdx) $ - Set.toList (getDependencyInstalledPackageIds lbi) - where - pkgIdx = installedPkgs lbi - - --------------------------------------------------------------------------------- -groupByLicense - :: [InstalledPackageInfo] - -> [(License, [InstalledPackageInfo])] -groupByLicense = foldl' - (\assoc ipi -> insertAList (license ipi) ipi assoc) [] - where - -- 'Cabal.License' doesn't have an 'Ord' instance so we need to use an - -- association list instead of 'Map'. The number of licenses probably won't - -- exceed 100 so I think we're alright. - insertAList :: Eq k => k -> v -> [(k, [v])] -> [(k, [v])] - insertAList k v [] = [(k, [v])] - insertAList k v ((k', vs) : kvs) - | k == k' = (k, v : vs) : kvs - | otherwise = (k', vs) : insertAList k v kvs - - --------------------------------------------------------------------------------- -displayDependencyLicenseList - :: [(License, [InstalledPackageInfo])] - -> [(String, [(String, Version)])] -displayDependencyLicenseList = - map (display *** map (getName &&& getVersion)) - where - getName = - display . pkgName . sourcePackageId - getVersion = - pkgVersion . sourcePackageId diff --git a/CabalHelper/Runtime/Main.hs b/CabalHelper/Runtime/Main.hs deleted file mode 100644 index 86bf169..0000000 --- a/CabalHelper/Runtime/Main.hs +++ /dev/null @@ -1,539 +0,0 @@ --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-# LANGUAGE CPP, BangPatterns, RecordWildCards, RankNTypes, ViewPatterns #-} -{-# OPTIONS_GHC -fno-warn-deprecations #-} - -#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) -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP CABAL_MAJOR == 1 && CABAL_MINOR >= 25 -import Distribution.PackageDescription (unFlagName, mkFlagName) -#endif -import Distribution.PackageDescription.Parse (readPackageDescription) -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) -#if CH_MIN_VERSION_Cabal(1,23,0) --- >= 1.23 -import Distribution.Simple.LocalBuildInfo (localUnitId) -#else --- <= 1.22 -import Distribution.Simple.LocalBuildInfo (inplacePackageId) -#endif - -import Distribution.Simple.GHC (componentGhcOptions) -import Distribution.Simple.Program.GHC (GhcOptions(..), renderGhcOptions) - -import Distribution.Simple.Setup (ConfigFlags(..),Flag(..)) -import Distribution.Simple.Build (initialBuildSteps) -import Distribution.Simple.BuildPaths (autogenModuleName, cppHeaderName, exeExtension) -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(2,0,0) --- CPP >= 2.0 -import Distribution.Version (versionNumbers, mkVersion) -#endif - -#if CH_MIN_VERSION_Cabal(1,22,0) --- CPP >= 1.22 -import Distribution.Utils.NubList -#endif - -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 -import Distribution.Types.ForeignLib (ForeignLib(..)) -import Distribution.Types.UnqualComponentName (unUnqualComponentName) -#endif - -#if CH_MIN_VERSION_Cabal(2,0,0) -import Distribution.Types.UnitId (UnitId) -import Distribution.Types.MungedPackageId (MungedPackageId) -#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 - -import CabalHelper.Runtime.Licenses - -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" - ++" | source-dirs\n" - ++" | licenses\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" - , "source-dirs" - , "licenses"] - -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 $$ \cmd -> do - case cmd of - "flags":[] -> do - return $ Just $ ChResponseFlags $ sort $ - map (flagName' &&& flagDefault) $ genPackageFlags gpd - - "config-flags":[] -> do - return $ Just $ ChResponseFlags $ sort $ - map (first unFlagName) $ configConfigurationsFlags $ configFlags lbi - - "non-default-config-flags":[] -> do - let flagDefinitons = genPackageFlags gpd - flagAssgnments = configConfigurationsFlags $ configFlags lbi - nonDefaultFlags = - [ (fn, v) - | MkFlag {flagName=(unFlagName -> fn), flagDefault=dv} <- flagDefinitons - , (unFlagName -> fn', v) <- flagAssgnments - , fn == fn' - , v /= dv - ] - 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 - let pd = localPkgDescr lbi - 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 - eps <- componentsMap lbi v distdir $ \c clbi bi -> - return $ componentEntrypoints c - -- MUST append Setup component at the end otherwise CabalHelper gets - -- confused - let eps' = eps ++ [(ChSetupHsName, ChSetupEntrypoint)] - return $ Just $ ChResponseEntrypoints eps' - - "source-dirs":[] -> do - res <- componentsMap lbi v distdir $$ \_ _ bi -> return $ hsSourceDirs bi - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "licenses":[] -> do - return $ Just $ ChResponseLicenses $ - map (second (map (second toDataVersion))) $ - displayDependencyLicenseList $ - groupByLicense $ getDependencyInstalledPackageInfos lbi - - "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 - -#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 - -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 - - -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 - writeIORef lr $ (componentNameToCh name, r):l' - - reverse <$> readIORef lr - -componentOptions' (lbi, v, distdir) inplaceFlag flags rf f = do - let pd = localPkgDescr lbi - 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) - [] -> removeInplaceDeps v lbi pd clbi - 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 - -componentNameToCh CLibName = ChLibName -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 -componentNameToCh (CSubLibName n) = ChSubLibName $ unUnqualComponentName' n -componentNameToCh (CFLibName n) = ChFLibName $ unUnqualComponentName' n -#endif -componentNameToCh (CExeName n) = ChExeName $ unUnqualComponentName' n -componentNameToCh (CTestName n) = ChTestName $ unUnqualComponentName' n -componentNameToCh (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 -componentOutDir lbi (CExe Executable {..})= exeOutDir lbi (unUnqualComponentName' exeName) -componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteExeV10 _ _, ..}) = - exeOutDir lbi (unUnqualComponentName' testName) -componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteLibV09 _ _, ..}) = - exeOutDir lbi (unUnqualComponentName' testName ++ "Stub") -componentOutDir lbi (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ _, ..})= - exeOutDir lbi (unUnqualComponentName' benchmarkName) - -gmModuleName :: C.ModuleName -> ChModuleName -gmModuleName = ChModuleName . intercalate "." . components - -componentEntrypoints :: Component -> ChEntrypoint -componentEntrypoints (CLib Library {..}) - = ChLibEntrypoint - (map gmModuleName exposedModules) - (map gmModuleName $ otherModules libBuildInfo) -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 [] [] - -exeOutDir :: LocalBuildInfo -> String -> FilePath -exeOutDir lbi exeName' = - ----- Copied from Distribution/Simple/GHC.hs:buildOrReplExe - let targetDir = (buildDir lbi) exeName' - exeDir = targetDir (exeName' ++ "-tmp") - in exeDir - - -removeInplaceDeps :: Verbosity - -> LocalBuildInfo - -> PackageDescription - -> ComponentLocalBuildInfo - -> (ComponentLocalBuildInfo, GhcOptions) -removeInplaceDeps v lbi pd clbi = let - (ideps, deps) = partition isInplaceDep (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) - - where -#if CH_MIN_VERSION_Cabal(2,0,0) - isInplaceDep :: (UnitId, MungedPackageId) -> Bool - isInplaceDep (mpid, pid) = localUnitId lbi == mpid -#else - isInplaceDep :: (InstalledPackageId, PackageId) -> Bool -# if CH_MIN_VERSION_Cabal(1,23,0) --- CPP >= 1.23 - isInplaceDep (ipid, pid) = localUnitId lbi == ipid -# else --- CPP <= 1.22 - isInplaceDep (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] -renderGhcOptions' lbi v opts = do -#if !CH_MIN_VERSION_Cabal(1,20,0) --- 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) --- CPP >= 1.20 && < 1.24 - return $ renderGhcOptions (compiler lbi) opts -#else --- CPP >= 1.24 - return $ renderGhcOptions (compiler lbi) (hostPlatform lbi) opts -#endif - -initialBuildStepsForAllComponents distdir pd lbi v = - initialBuildSteps distdir pd lbi v diff --git a/CabalHelper/Shared/Common.hs b/CabalHelper/Shared/Common.hs deleted file mode 100644 index 239fe3c..0000000 --- a/CabalHelper/Shared/Common.hs +++ /dev/null @@ -1,128 +0,0 @@ --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-| -Module : CabalHelper.Shared.Common -Description : Shared utility functions -License : AGPL-3 --} - -{-# LANGUAGE DeriveDataTypeable, OverloadedStrings #-} -module CabalHelper.Shared.Common where - -import Control.Applicative -import Control.Exception as E -import Control.Monad -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 -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 - -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 diff --git a/CabalHelper/Shared/InterfaceTypes.hs b/CabalHelper/Shared/InterfaceTypes.hs deleted file mode 100644 index 5f4972f..0000000 --- a/CabalHelper/Shared/InterfaceTypes.hs +++ /dev/null @@ -1,75 +0,0 @@ --- 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 Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero 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 : AGPL-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_DIR/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)] - | 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] - } - | ChExeEntrypoint { chMainIs :: FilePath - , chOtherModules :: [ChModuleName] - } deriving (Eq, Ord, Read, Show, Generic) - -data ChPkgDb = ChPkgGlobal - | ChPkgUser - | ChPkgSpecific FilePath - deriving (Eq, Ord, Read, Show, Generic) diff --git a/CabalHelper/Shared/Sandbox.hs b/CabalHelper/Shared/Sandbox.hs deleted file mode 100644 index 4dd9705..0000000 --- a/CabalHelper/Shared/Sandbox.hs +++ /dev/null @@ -1,77 +0,0 @@ --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-| -Module : CabalHelper.Shared.Sandbox -Description : Extracting information from @cabal.sandbox.config@ files -License : AGPL-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) [] diff --git a/Distribution/Helper.hs b/Distribution/Helper.hs deleted file mode 100644 index 73ad668..0000000 --- a/Distribution/Helper.hs +++ /dev/null @@ -1,527 +0,0 @@ --- ghc-mod: Making Haskell development *more* fun --- 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 Affero 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 Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-# LANGUAGE CPP, RecordWildCards, FlexibleContexts, ConstraintKinds, - GeneralizedNewtypeDeriving, DeriveDataTypeable, DeriveGeneric, DeriveFunctor - #-} - -{-| -Module : Distribution.Helper -License : AGPL-3 -Maintainer : dxld@darkboxed.org -Portability : POSIX --} - -module Distribution.Helper ( - -- * Running Queries - Query - , runQuery - - -- * Queries against Cabal\'s on disk state - - -- ** Package queries - , packageId - , packageDbStack - , packageFlags - , packageLicenses - , compilerVersion - - , ghcMergedPkgOptions - - -- ** cabal-install queries - , configFlags - , nonDefaultConfigFlags - - - -- ** Component queries - , ComponentQuery - , components - - , ghcSrcOptions - , ghcPkgOptions - , ghcLangOptions - , ghcOptions - , sourceDirs - , entrypoints - - -- * Query environment - , QueryEnv - , mkQueryEnv - , qeReadProcess - , qePrograms - , qeProjectDir - , qeDistDir - , qeCabalPkgDb - , qeCabalVer - - , Programs(..) - , defaultPrograms - - - -- * Result types - , ChModuleName(..) - , ChComponentName(..) - , ChPkgDb(..) - , ChEntrypoint(..) - - -- * General information - , buildPlatform - - -- * Stuff that cabal-install really should export - , Distribution.Helper.getSandboxPkgDb - - -- * Managing @dist/@ - , prepare - , reconfigure - , writeAutogenFiles - - -- * $libexec related error handling - , LibexecNotFoundError(..) - , libexecNotFoundError - - -- * Reexports - , module Data.Functor.Apply - ) where - -import Control.Applicative -import Control.Monad -import Control.Monad.IO.Class -import Control.Monad.State.Strict -import Control.Monad.Reader -import Control.Exception as E -import Data.Char -import Data.List -import Data.Maybe -import Data.Version -import Data.Typeable -import Data.Functor.Apply -import Distribution.Simple.BuildPaths (exeExtension) -import System.Environment -import System.FilePath hiding ((<.>)) -import qualified System.FilePath as FP -import System.Directory -import System.Process -import System.IO.Unsafe -import Text.Printf -import GHC.Generics -import Prelude - -import Paths_cabal_helper (getLibexecDir) -import CabalHelper.Shared.InterfaceTypes -import CabalHelper.Shared.Sandbox - --- | Paths or names of various programs we need. -data Programs = Programs { - -- | The path to the @cabal@ program. - cabalProgram :: FilePath, - - -- | The path to the @ghc@ program. - ghcProgram :: FilePath, - - -- | The path to the @ghc-pkg@ program. If - -- not changed it will be derived from the path to 'ghcProgram'. - ghcPkgProgram :: FilePath - } deriving (Eq, Ord, Show, Read, Generic, Typeable) - --- | Default all programs to their unqualified names, i.e. they will be searched --- for on @PATH@. -defaultPrograms :: Programs -defaultPrograms = Programs "cabal" "ghc" "ghc-pkg" - --- | Environment for running a 'Query'. The real constructor is not exposed, --- the field accessors are however. See below. Use the 'mkQueryEnv' smart --- constructor to construct one. -data QueryEnv = QueryEnv { - -- | Field accessor for 'QueryEnv'. Defines how to start the cabal-helper - -- process. Useful if you need to capture stderr output from the helper. - qeReadProcess :: FilePath -> [String] -> String -> IO String, - - -- | Field accessor for 'QueryEnv'. - qePrograms :: Programs, - - -- | Field accessor for 'QueryEnv'. Defines path to the project directory, - -- i.e. a directory containing a @project.cabal@ file - qeProjectDir :: FilePath, - - - -- | Field accessor for 'QueryEnv'. Defines path to the @dist/@ directory, - -- /builddir/ in Cabal terminology. - qeDistDir :: FilePath, - - -- | Field accessor for 'QueryEnv'. Defines where to look for the Cabal - -- library when linking the helper. - qeCabalPkgDb :: Maybe FilePath, - - -- | Field accessor for 'QueryEnv'. If @dist/setup-config@ wasn\'t written - -- by this version of Cabal an error is thrown when running the query. - qeCabalVer :: Maybe Version - } - --- | @mkQueryEnv projdir distdir@. Smart constructor for 'QueryEnv'. --- Sets fields 'qeProjectDir' and 'qeDistDir' to @projdir@ and @distdir@ --- respectively and provides sensible defaults for the other fields. -mkQueryEnv :: FilePath - -- ^ Path to the project directory, i.e. the directory containing a - -- @project.cabal@ file - -> FilePath - -- ^ Path to the @dist/@ directory, called /builddir/ in Cabal - -- terminology. - -> QueryEnv -mkQueryEnv projdir distdir = QueryEnv { - qeReadProcess = readProcess - , qePrograms = defaultPrograms - , qeProjectDir = projdir - , qeDistDir = distdir - , qeCabalPkgDb = Nothing - , qeCabalVer = Nothing - } - -data SomeLocalBuildInfo = SomeLocalBuildInfo { - slbiPackageDbStack :: [ChPkgDb], - slbiPackageFlags :: [(String, Bool)], - slbiPkgLicenses :: [(String, [(String, Version)])], - slbiCompilerVersion :: (String, Version), - - slbiGhcMergedPkgOptions :: [String], - - slbiConfigFlags :: [(String, Bool)], - slbiNonDefaultConfigFlags :: [(String, Bool)], - - slbiGhcSrcOptions :: [(ChComponentName, [String])], - slbiGhcPkgOptions :: [(ChComponentName, [String])], - slbiGhcLangOptions :: [(ChComponentName, [String])], - slbiGhcOptions :: [(ChComponentName, [String])], - - slbiSourceDirs :: [(ChComponentName, [String])], - slbiEntrypoints :: [(ChComponentName, ChEntrypoint)] - } deriving (Eq, Ord, Read, Show) - --- | A lazy, cached, query against a package's Cabal configuration. Use --- 'runQuery' to execute it. -newtype Query m a = Query { unQuery :: StateT (Maybe SomeLocalBuildInfo) - (ReaderT QueryEnv m) a } - deriving (Functor, Applicative, Monad, MonadIO) - -instance MonadTrans Query where - lift = Query . lift . lift - -type MonadQuery m = ( MonadIO m - , MonadState (Maybe SomeLocalBuildInfo) m - , MonadReader QueryEnv m) - --- | A 'Query' to run on all components of a package. Use 'components' to get a --- regular 'Query'. -newtype ComponentQuery m a = ComponentQuery (Query m [(ChComponentName, a)]) - deriving (Functor) - -instance Monad m => Apply (ComponentQuery m) where - ComponentQuery flab <.> ComponentQuery fla = - ComponentQuery $ liftM2 go flab fla - where - go :: [(ChComponentName, a -> b)] - -> [(ChComponentName, a)] - -> [(ChComponentName, b)] - go lab la = - [ (cn, ab a) - | (cn, ab) <- lab - , (cn', a) <- la - , cn == cn' - ] - -run :: Monad m => QueryEnv -> Maybe SomeLocalBuildInfo -> Query m a -> m a -run e s action = flip runReaderT e (flip evalStateT s (unQuery action)) - --- | @runQuery env query@. Run a 'Query' under a given 'QueryEnv'. -runQuery :: Monad m - => QueryEnv - -> Query m a - -> m a -runQuery qe action = run qe Nothing action - -getSlbi :: MonadQuery m => m SomeLocalBuildInfo -getSlbi = do - s <- get - case s of - Nothing -> do - slbi <- getSomeConfigState - put (Just slbi) - return slbi - Just slbi -> return slbi - --- | List of package databases to use. -packageDbStack :: MonadIO m => Query m [ChPkgDb] - --- | Like @ghcPkgOptions@ but for the whole package not just one component -ghcMergedPkgOptions :: MonadIO m => Query m [String] - --- | Get the licenses of the packages the current project is linking against. -packageLicenses :: MonadIO m => Query m [(String, [(String, Version)])] - --- | Flag definitions from cabal file -packageFlags :: MonadIO m => Query m [(String, Bool)] - --- | Flag assignments from setup-config -configFlags :: MonadIO m => Query m [(String, Bool)] - --- | Flag assignments from setup-config which differ from the default --- setting. This can also include flags which cabal decided to modify, --- i.e. don't rely on these being the flags set by the user directly. -nonDefaultConfigFlags :: MonadIO m => Query m [(String, Bool)] - --- | The version of GHC the project is configured to use -compilerVersion :: MonadIO m => Query m (String, Version) - --- | Package identifier, i.e. package name and version -packageId :: MonadIO m => Query m (String, Version) - --- | Run a ComponentQuery on all components of the package. -components :: Monad m => ComponentQuery m (ChComponentName -> b) -> Query m [b] -components (ComponentQuery sc) = map (\(cn, f) -> f cn) <$> sc - --- | Modules or files Cabal would have the compiler build directly. Can be used --- to compute the home module closure for a component. -entrypoints :: MonadIO m => ComponentQuery m ChEntrypoint - --- | A component's @source-dirs@ field, beware since if this is empty implicit --- behaviour in GHC kicks in. -sourceDirs :: MonadIO m => ComponentQuery m [FilePath] - --- | All options Cabal would pass to GHC. -ghcOptions :: MonadIO m => ComponentQuery m [String] - --- | Only search path related GHC options. -ghcSrcOptions :: MonadIO m => ComponentQuery m [String] - --- | Only package related GHC options, sufficient for things don't need to --- access any home modules. -ghcPkgOptions :: MonadIO m => ComponentQuery m [String] - --- | Only language related options, i.e. @-XSomeExtension@ -ghcLangOptions :: MonadIO m => ComponentQuery m [String] - -packageId = Query $ getPackageId -packageDbStack = Query $ slbiPackageDbStack `liftM` getSlbi -packageFlags = Query $ slbiPackageFlags `liftM` getSlbi -packageLicenses = Query $ slbiPkgLicenses `liftM` getSlbi -compilerVersion = Query $ slbiCompilerVersion `liftM` getSlbi -ghcMergedPkgOptions = Query $ slbiGhcMergedPkgOptions `liftM` getSlbi -configFlags = Query $ slbiConfigFlags `liftM` getSlbi -nonDefaultConfigFlags = Query $ slbiNonDefaultConfigFlags `liftM` getSlbi - -ghcSrcOptions = ComponentQuery $ Query $ slbiGhcSrcOptions `liftM` getSlbi -ghcPkgOptions = ComponentQuery $ Query $ slbiGhcPkgOptions `liftM` getSlbi -ghcOptions = ComponentQuery $ Query $ slbiGhcOptions `liftM` getSlbi -ghcLangOptions = ComponentQuery $ Query $ slbiGhcLangOptions `liftM` getSlbi -sourceDirs = ComponentQuery $ Query $ slbiSourceDirs `liftM` getSlbi -entrypoints = ComponentQuery $ Query $ slbiEntrypoints `liftM` getSlbi - --- | Run @cabal configure@ -reconfigure :: MonadIO m - => (FilePath -> [String] -> String -> IO String) - -> Programs -- ^ Program paths - -> [String] -- ^ Command line arguments to be passed to @cabal@ - -> m () -reconfigure readProc progs cabalOpts = do - let progOpts = - [ "--with-ghc=" ++ ghcProgram progs ] - -- Only pass ghc-pkg if it was actually set otherwise we - -- might break cabal's guessing logic - ++ if ghcPkgProgram progs /= "ghc-pkg" - then [ "--with-ghc-pkg=" ++ ghcPkgProgram progs ] - else [] - ++ cabalOpts - _ <- liftIO $ readProc (cabalProgram progs) ("configure":progOpts) "" - return () - -readHelper :: (MonadIO m, MonadQuery m) => [String] -> m [Maybe ChResponse] -readHelper args = ask >>= \qe -> liftIO $ do - out <- either error id <$> invokeHelper qe args - let res = read out - liftIO $ evaluate res `E.catch` \se@(SomeException _) -> do - md <- lookupEnv' "CABAL_HELPER_DEBUG" - let msg = "readHelper: exception: '" ++ show se ++ "'" - error $ msg ++ case md of - Nothing -> ", for more information set the environment variable CABAL_HELPER_DEBUG" - Just _ -> ", output: '"++ out ++"'" - -invokeHelper :: QueryEnv -> [String] -> IO (Either String String) -invokeHelper QueryEnv {..} args = do - let progArgs = [ "--with-ghc=" ++ ghcProgram qePrograms - , "--with-ghc-pkg=" ++ ghcPkgProgram qePrograms - , "--with-cabal=" ++ cabalProgram qePrograms - ] - exe <- findLibexecExe - let args' = progArgs ++ qeProjectDir:qeDistDir:args - out <- qeReadProcess exe args' "" - (Right <$> evaluate out) `E.catch` \(SomeException _) -> - return $ Left $ concat - ["invokeHelper", ": ", exe, " " - , intercalate " " (map show args') - , " failed" - ] - -getPackageId :: MonadQuery m => m (String, Version) -getPackageId = ask >>= \QueryEnv {..} -> do - [ Just (ChResponseVersion pkgName pkgVer) ] <- readHelper [ "package-id" ] - return (pkgName, pkgVer) - -getSomeConfigState :: MonadQuery m => m SomeLocalBuildInfo -getSomeConfigState = ask >>= \QueryEnv {..} -> do - res <- readHelper - [ "package-db-stack" - , "flags" - , "licenses" - , "compiler-version" - - , "ghc-merged-pkg-options" - - , "config-flags" - , "non-default-config-flags" - - , "ghc-src-options" - , "ghc-pkg-options" - , "ghc-lang-options" - , "ghc-options" - - , "source-dirs" - , "entrypoints" - ] - let [ Just (ChResponsePkgDbs slbiPackageDbStack), - Just (ChResponseFlags slbiPackageFlags), - Just (ChResponseLicenses slbiPkgLicenses), - Just (ChResponseVersion comp compVer), - - Just (ChResponseList slbiGhcMergedPkgOptions), - - Just (ChResponseFlags slbiConfigFlags), - Just (ChResponseFlags slbiNonDefaultConfigFlags), - - Just (ChResponseCompList slbiGhcSrcOptions), - Just (ChResponseCompList slbiGhcPkgOptions), - Just (ChResponseCompList slbiGhcLangOptions), - Just (ChResponseCompList slbiGhcOptions), - - Just (ChResponseCompList slbiSourceDirs), - Just (ChResponseEntrypoints slbiEntrypoints) - ] = res - slbiCompilerVersion = (comp, compVer) - return $ SomeLocalBuildInfo {..} - - --- | Make sure the appropriate helper executable for the given project is --- installed and ready to run queries. -prepare :: MonadIO m => QueryEnv -> m () -prepare qe = - liftIO $ void $ invokeHelper qe [] - --- | Create @cabal_macros.h@ and @Paths_\@ possibly other generated files --- in the usual place. -writeAutogenFiles :: MonadIO m => QueryEnv -> m () -writeAutogenFiles qe = - liftIO $ void $ invokeHelper qe ["write-autogen-files"] - --- | Get the path to the sandbox package-db in a project -getSandboxPkgDb :: (FilePath -> [String] -> String -> IO String) - -> FilePath - -- ^ Cabal build platform, i.e. @buildPlatform@ - -> Version - -- ^ GHC version (@cProjectVersion@ is your friend) - -> IO (Maybe FilePath) -getSandboxPkgDb readProc = - CabalHelper.Shared.Sandbox.getSandboxPkgDb $ unsafePerformIO $ buildPlatform readProc - -buildPlatform :: (FilePath -> [String] -> String -> IO String) -> IO String -buildPlatform readProc = do - exe <- findLibexecExe - CabalHelper.Shared.Sandbox.dropWhileEnd isSpace <$> readProc exe ["print-build-platform"] "" - --- | This exception is thrown by all 'runQuery' functions if the internal --- wrapper executable cannot be found. You may catch this and present the user --- an appropriate error message however the default is to print --- 'libexecNotFoundError'. -data LibexecNotFoundError = LibexecNotFoundError String FilePath - deriving (Typeable) -instance Exception LibexecNotFoundError -instance Show LibexecNotFoundError where - show (LibexecNotFoundError exe dir) = - libexecNotFoundError exe dir "https://github.com/DanielG/cabal-helper/issues" - -findLibexecExe :: IO FilePath -findLibexecExe = do - libexecdir <- getLibexecDir - let exeName = "cabal-helper-wrapper" - exe = libexecdir exeName FP.<.> exeExtension' - - exists <- doesFileExist exe - - if exists - then return exe - else do - mdir <- tryFindCabalHelperTreeLibexecDir - case mdir of - Nothing -> - error $ throw $ LibexecNotFoundError exeName libexecdir - Just dir -> - return $ dir "dist" "build" exeName exeName - -tryFindCabalHelperTreeLibexecDir :: IO (Maybe FilePath) -tryFindCabalHelperTreeLibexecDir = do - exe <- getExecutablePath' - dir <- case takeFileName exe of - "ghc" -> do -- we're probably in ghci; try CWD - getCurrentDirectory - _ -> - return $ (!!4) $ iterate takeDirectory exe - exists <- doesFileExist $ dir "cabal-helper.cabal" - return $ if exists - then Just dir - else Nothing - -libexecNotFoundError :: String -- ^ Name of the executable we were trying to - -- find - -> FilePath -- ^ Path to @$libexecdir@ - -> String -- ^ URL the user will be directed towards to - -- report a bug. - -> String -libexecNotFoundError exe dir reportBug = printf - ( "Could not find $libexecdir/%s\n" - ++"\n" - ++"If you are a cabal-helper developer you can set the environment variable\n" - ++"`cabal_helper_libexecdir' to override $libexecdir[1]. The following will\n" - ++"work in the cabal-helper source tree:\n" - ++"\n" - ++" $ export cabal_helper_libexecdir=$PWD/dist/build/%s\n" - ++"\n" - ++"[1]: %s\n" - ++"\n" - ++"If you don't know what I'm talking about something went wrong with your\n" - ++"installation. Please report this problem here:\n" - ++"\n" - ++" %s") exe exe dir reportBug - -getExecutablePath' :: IO FilePath -getExecutablePath' = -#if MIN_VERSION_base(4,6,0) - getExecutablePath -#else - getProgName -#endif - -lookupEnv' :: String -> IO (Maybe String) -lookupEnv' k = lookup k <$> getEnvironment - -exeExtension' :: FilePath -exeExtension' = Distribution.Simple.BuildPaths.exeExtension diff --git a/cabal-helper.cabal b/cabal-helper.cabal index 07aadb4..85998fc 100644 --- a/cabal-helper.cabal +++ b/cabal-helper.cabal @@ -33,7 +33,7 @@ category: Distribution build-type: Custom cabal-version: >=1.14 extra-source-files: README.md - CabalHelper/Runtime/*.hs + src/CabalHelper/Runtime/*.hs source-repository head type: git @@ -48,6 +48,7 @@ custom-setup library default-language: Haskell2010 default-extensions: NondecreasingIndentation + hs-source-dirs: lib, src exposed-modules: Distribution.Helper other-modules: CabalHelper.Shared.InterfaceTypes @@ -69,6 +70,7 @@ executable cabal-helper-wrapper default-extensions: NondecreasingIndentation other-extensions: TemplateHaskell main-is: CabalHelper/Compiletime/Wrapper.hs + hs-source-dirs: src other-modules: CabalHelper.Compiletime.Compat.Environment CabalHelper.Compiletime.Compat.Version @@ -105,7 +107,8 @@ test-suite compile-test default-language: Haskell2010 default-extensions: NondecreasingIndentation type: exitcode-stdio-1.0 - main-is: tests/CompileTest.hs + main-is: CompileTest.hs + hs-source-dirs: tests, src other-modules: CabalHelper.Compiletime.Compat.Environment CabalHelper.Compiletime.Compat.Version @@ -116,7 +119,6 @@ test-suite compile-test CabalHelper.Shared.Common CabalHelper.Shared.Sandbox Paths_cabal_helper - hs-source-dirs: . ghc-options: -Wall build-tools: cabal @@ -144,6 +146,7 @@ executable cabal-helper-main else buildable: False main-is: CabalHelper/Runtime/Main.hs + hs-source-dirs: src other-modules: CabalHelper.Runtime.Licenses CabalHelper.Shared.Common diff --git a/lib/Distribution/Helper.hs b/lib/Distribution/Helper.hs new file mode 100644 index 0000000..73ad668 --- /dev/null +++ b/lib/Distribution/Helper.hs @@ -0,0 +1,527 @@ +-- ghc-mod: Making Haskell development *more* fun +-- 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 Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP, RecordWildCards, FlexibleContexts, ConstraintKinds, + GeneralizedNewtypeDeriving, DeriveDataTypeable, DeriveGeneric, DeriveFunctor + #-} + +{-| +Module : Distribution.Helper +License : AGPL-3 +Maintainer : dxld@darkboxed.org +Portability : POSIX +-} + +module Distribution.Helper ( + -- * Running Queries + Query + , runQuery + + -- * Queries against Cabal\'s on disk state + + -- ** Package queries + , packageId + , packageDbStack + , packageFlags + , packageLicenses + , compilerVersion + + , ghcMergedPkgOptions + + -- ** cabal-install queries + , configFlags + , nonDefaultConfigFlags + + + -- ** Component queries + , ComponentQuery + , components + + , ghcSrcOptions + , ghcPkgOptions + , ghcLangOptions + , ghcOptions + , sourceDirs + , entrypoints + + -- * Query environment + , QueryEnv + , mkQueryEnv + , qeReadProcess + , qePrograms + , qeProjectDir + , qeDistDir + , qeCabalPkgDb + , qeCabalVer + + , Programs(..) + , defaultPrograms + + + -- * Result types + , ChModuleName(..) + , ChComponentName(..) + , ChPkgDb(..) + , ChEntrypoint(..) + + -- * General information + , buildPlatform + + -- * Stuff that cabal-install really should export + , Distribution.Helper.getSandboxPkgDb + + -- * Managing @dist/@ + , prepare + , reconfigure + , writeAutogenFiles + + -- * $libexec related error handling + , LibexecNotFoundError(..) + , libexecNotFoundError + + -- * Reexports + , module Data.Functor.Apply + ) where + +import Control.Applicative +import Control.Monad +import Control.Monad.IO.Class +import Control.Monad.State.Strict +import Control.Monad.Reader +import Control.Exception as E +import Data.Char +import Data.List +import Data.Maybe +import Data.Version +import Data.Typeable +import Data.Functor.Apply +import Distribution.Simple.BuildPaths (exeExtension) +import System.Environment +import System.FilePath hiding ((<.>)) +import qualified System.FilePath as FP +import System.Directory +import System.Process +import System.IO.Unsafe +import Text.Printf +import GHC.Generics +import Prelude + +import Paths_cabal_helper (getLibexecDir) +import CabalHelper.Shared.InterfaceTypes +import CabalHelper.Shared.Sandbox + +-- | Paths or names of various programs we need. +data Programs = Programs { + -- | The path to the @cabal@ program. + cabalProgram :: FilePath, + + -- | The path to the @ghc@ program. + ghcProgram :: FilePath, + + -- | The path to the @ghc-pkg@ program. If + -- not changed it will be derived from the path to 'ghcProgram'. + ghcPkgProgram :: FilePath + } deriving (Eq, Ord, Show, Read, Generic, Typeable) + +-- | Default all programs to their unqualified names, i.e. they will be searched +-- for on @PATH@. +defaultPrograms :: Programs +defaultPrograms = Programs "cabal" "ghc" "ghc-pkg" + +-- | Environment for running a 'Query'. The real constructor is not exposed, +-- the field accessors are however. See below. Use the 'mkQueryEnv' smart +-- constructor to construct one. +data QueryEnv = QueryEnv { + -- | Field accessor for 'QueryEnv'. Defines how to start the cabal-helper + -- process. Useful if you need to capture stderr output from the helper. + qeReadProcess :: FilePath -> [String] -> String -> IO String, + + -- | Field accessor for 'QueryEnv'. + qePrograms :: Programs, + + -- | Field accessor for 'QueryEnv'. Defines path to the project directory, + -- i.e. a directory containing a @project.cabal@ file + qeProjectDir :: FilePath, + + + -- | Field accessor for 'QueryEnv'. Defines path to the @dist/@ directory, + -- /builddir/ in Cabal terminology. + qeDistDir :: FilePath, + + -- | Field accessor for 'QueryEnv'. Defines where to look for the Cabal + -- library when linking the helper. + qeCabalPkgDb :: Maybe FilePath, + + -- | Field accessor for 'QueryEnv'. If @dist/setup-config@ wasn\'t written + -- by this version of Cabal an error is thrown when running the query. + qeCabalVer :: Maybe Version + } + +-- | @mkQueryEnv projdir distdir@. Smart constructor for 'QueryEnv'. +-- Sets fields 'qeProjectDir' and 'qeDistDir' to @projdir@ and @distdir@ +-- respectively and provides sensible defaults for the other fields. +mkQueryEnv :: FilePath + -- ^ Path to the project directory, i.e. the directory containing a + -- @project.cabal@ file + -> FilePath + -- ^ Path to the @dist/@ directory, called /builddir/ in Cabal + -- terminology. + -> QueryEnv +mkQueryEnv projdir distdir = QueryEnv { + qeReadProcess = readProcess + , qePrograms = defaultPrograms + , qeProjectDir = projdir + , qeDistDir = distdir + , qeCabalPkgDb = Nothing + , qeCabalVer = Nothing + } + +data SomeLocalBuildInfo = SomeLocalBuildInfo { + slbiPackageDbStack :: [ChPkgDb], + slbiPackageFlags :: [(String, Bool)], + slbiPkgLicenses :: [(String, [(String, Version)])], + slbiCompilerVersion :: (String, Version), + + slbiGhcMergedPkgOptions :: [String], + + slbiConfigFlags :: [(String, Bool)], + slbiNonDefaultConfigFlags :: [(String, Bool)], + + slbiGhcSrcOptions :: [(ChComponentName, [String])], + slbiGhcPkgOptions :: [(ChComponentName, [String])], + slbiGhcLangOptions :: [(ChComponentName, [String])], + slbiGhcOptions :: [(ChComponentName, [String])], + + slbiSourceDirs :: [(ChComponentName, [String])], + slbiEntrypoints :: [(ChComponentName, ChEntrypoint)] + } deriving (Eq, Ord, Read, Show) + +-- | A lazy, cached, query against a package's Cabal configuration. Use +-- 'runQuery' to execute it. +newtype Query m a = Query { unQuery :: StateT (Maybe SomeLocalBuildInfo) + (ReaderT QueryEnv m) a } + deriving (Functor, Applicative, Monad, MonadIO) + +instance MonadTrans Query where + lift = Query . lift . lift + +type MonadQuery m = ( MonadIO m + , MonadState (Maybe SomeLocalBuildInfo) m + , MonadReader QueryEnv m) + +-- | A 'Query' to run on all components of a package. Use 'components' to get a +-- regular 'Query'. +newtype ComponentQuery m a = ComponentQuery (Query m [(ChComponentName, a)]) + deriving (Functor) + +instance Monad m => Apply (ComponentQuery m) where + ComponentQuery flab <.> ComponentQuery fla = + ComponentQuery $ liftM2 go flab fla + where + go :: [(ChComponentName, a -> b)] + -> [(ChComponentName, a)] + -> [(ChComponentName, b)] + go lab la = + [ (cn, ab a) + | (cn, ab) <- lab + , (cn', a) <- la + , cn == cn' + ] + +run :: Monad m => QueryEnv -> Maybe SomeLocalBuildInfo -> Query m a -> m a +run e s action = flip runReaderT e (flip evalStateT s (unQuery action)) + +-- | @runQuery env query@. Run a 'Query' under a given 'QueryEnv'. +runQuery :: Monad m + => QueryEnv + -> Query m a + -> m a +runQuery qe action = run qe Nothing action + +getSlbi :: MonadQuery m => m SomeLocalBuildInfo +getSlbi = do + s <- get + case s of + Nothing -> do + slbi <- getSomeConfigState + put (Just slbi) + return slbi + Just slbi -> return slbi + +-- | List of package databases to use. +packageDbStack :: MonadIO m => Query m [ChPkgDb] + +-- | Like @ghcPkgOptions@ but for the whole package not just one component +ghcMergedPkgOptions :: MonadIO m => Query m [String] + +-- | Get the licenses of the packages the current project is linking against. +packageLicenses :: MonadIO m => Query m [(String, [(String, Version)])] + +-- | Flag definitions from cabal file +packageFlags :: MonadIO m => Query m [(String, Bool)] + +-- | Flag assignments from setup-config +configFlags :: MonadIO m => Query m [(String, Bool)] + +-- | Flag assignments from setup-config which differ from the default +-- setting. This can also include flags which cabal decided to modify, +-- i.e. don't rely on these being the flags set by the user directly. +nonDefaultConfigFlags :: MonadIO m => Query m [(String, Bool)] + +-- | The version of GHC the project is configured to use +compilerVersion :: MonadIO m => Query m (String, Version) + +-- | Package identifier, i.e. package name and version +packageId :: MonadIO m => Query m (String, Version) + +-- | Run a ComponentQuery on all components of the package. +components :: Monad m => ComponentQuery m (ChComponentName -> b) -> Query m [b] +components (ComponentQuery sc) = map (\(cn, f) -> f cn) <$> sc + +-- | Modules or files Cabal would have the compiler build directly. Can be used +-- to compute the home module closure for a component. +entrypoints :: MonadIO m => ComponentQuery m ChEntrypoint + +-- | A component's @source-dirs@ field, beware since if this is empty implicit +-- behaviour in GHC kicks in. +sourceDirs :: MonadIO m => ComponentQuery m [FilePath] + +-- | All options Cabal would pass to GHC. +ghcOptions :: MonadIO m => ComponentQuery m [String] + +-- | Only search path related GHC options. +ghcSrcOptions :: MonadIO m => ComponentQuery m [String] + +-- | Only package related GHC options, sufficient for things don't need to +-- access any home modules. +ghcPkgOptions :: MonadIO m => ComponentQuery m [String] + +-- | Only language related options, i.e. @-XSomeExtension@ +ghcLangOptions :: MonadIO m => ComponentQuery m [String] + +packageId = Query $ getPackageId +packageDbStack = Query $ slbiPackageDbStack `liftM` getSlbi +packageFlags = Query $ slbiPackageFlags `liftM` getSlbi +packageLicenses = Query $ slbiPkgLicenses `liftM` getSlbi +compilerVersion = Query $ slbiCompilerVersion `liftM` getSlbi +ghcMergedPkgOptions = Query $ slbiGhcMergedPkgOptions `liftM` getSlbi +configFlags = Query $ slbiConfigFlags `liftM` getSlbi +nonDefaultConfigFlags = Query $ slbiNonDefaultConfigFlags `liftM` getSlbi + +ghcSrcOptions = ComponentQuery $ Query $ slbiGhcSrcOptions `liftM` getSlbi +ghcPkgOptions = ComponentQuery $ Query $ slbiGhcPkgOptions `liftM` getSlbi +ghcOptions = ComponentQuery $ Query $ slbiGhcOptions `liftM` getSlbi +ghcLangOptions = ComponentQuery $ Query $ slbiGhcLangOptions `liftM` getSlbi +sourceDirs = ComponentQuery $ Query $ slbiSourceDirs `liftM` getSlbi +entrypoints = ComponentQuery $ Query $ slbiEntrypoints `liftM` getSlbi + +-- | Run @cabal configure@ +reconfigure :: MonadIO m + => (FilePath -> [String] -> String -> IO String) + -> Programs -- ^ Program paths + -> [String] -- ^ Command line arguments to be passed to @cabal@ + -> m () +reconfigure readProc progs cabalOpts = do + let progOpts = + [ "--with-ghc=" ++ ghcProgram progs ] + -- Only pass ghc-pkg if it was actually set otherwise we + -- might break cabal's guessing logic + ++ if ghcPkgProgram progs /= "ghc-pkg" + then [ "--with-ghc-pkg=" ++ ghcPkgProgram progs ] + else [] + ++ cabalOpts + _ <- liftIO $ readProc (cabalProgram progs) ("configure":progOpts) "" + return () + +readHelper :: (MonadIO m, MonadQuery m) => [String] -> m [Maybe ChResponse] +readHelper args = ask >>= \qe -> liftIO $ do + out <- either error id <$> invokeHelper qe args + let res = read out + liftIO $ evaluate res `E.catch` \se@(SomeException _) -> do + md <- lookupEnv' "CABAL_HELPER_DEBUG" + let msg = "readHelper: exception: '" ++ show se ++ "'" + error $ msg ++ case md of + Nothing -> ", for more information set the environment variable CABAL_HELPER_DEBUG" + Just _ -> ", output: '"++ out ++"'" + +invokeHelper :: QueryEnv -> [String] -> IO (Either String String) +invokeHelper QueryEnv {..} args = do + let progArgs = [ "--with-ghc=" ++ ghcProgram qePrograms + , "--with-ghc-pkg=" ++ ghcPkgProgram qePrograms + , "--with-cabal=" ++ cabalProgram qePrograms + ] + exe <- findLibexecExe + let args' = progArgs ++ qeProjectDir:qeDistDir:args + out <- qeReadProcess exe args' "" + (Right <$> evaluate out) `E.catch` \(SomeException _) -> + return $ Left $ concat + ["invokeHelper", ": ", exe, " " + , intercalate " " (map show args') + , " failed" + ] + +getPackageId :: MonadQuery m => m (String, Version) +getPackageId = ask >>= \QueryEnv {..} -> do + [ Just (ChResponseVersion pkgName pkgVer) ] <- readHelper [ "package-id" ] + return (pkgName, pkgVer) + +getSomeConfigState :: MonadQuery m => m SomeLocalBuildInfo +getSomeConfigState = ask >>= \QueryEnv {..} -> do + res <- readHelper + [ "package-db-stack" + , "flags" + , "licenses" + , "compiler-version" + + , "ghc-merged-pkg-options" + + , "config-flags" + , "non-default-config-flags" + + , "ghc-src-options" + , "ghc-pkg-options" + , "ghc-lang-options" + , "ghc-options" + + , "source-dirs" + , "entrypoints" + ] + let [ Just (ChResponsePkgDbs slbiPackageDbStack), + Just (ChResponseFlags slbiPackageFlags), + Just (ChResponseLicenses slbiPkgLicenses), + Just (ChResponseVersion comp compVer), + + Just (ChResponseList slbiGhcMergedPkgOptions), + + Just (ChResponseFlags slbiConfigFlags), + Just (ChResponseFlags slbiNonDefaultConfigFlags), + + Just (ChResponseCompList slbiGhcSrcOptions), + Just (ChResponseCompList slbiGhcPkgOptions), + Just (ChResponseCompList slbiGhcLangOptions), + Just (ChResponseCompList slbiGhcOptions), + + Just (ChResponseCompList slbiSourceDirs), + Just (ChResponseEntrypoints slbiEntrypoints) + ] = res + slbiCompilerVersion = (comp, compVer) + return $ SomeLocalBuildInfo {..} + + +-- | Make sure the appropriate helper executable for the given project is +-- installed and ready to run queries. +prepare :: MonadIO m => QueryEnv -> m () +prepare qe = + liftIO $ void $ invokeHelper qe [] + +-- | Create @cabal_macros.h@ and @Paths_\@ possibly other generated files +-- in the usual place. +writeAutogenFiles :: MonadIO m => QueryEnv -> m () +writeAutogenFiles qe = + liftIO $ void $ invokeHelper qe ["write-autogen-files"] + +-- | Get the path to the sandbox package-db in a project +getSandboxPkgDb :: (FilePath -> [String] -> String -> IO String) + -> FilePath + -- ^ Cabal build platform, i.e. @buildPlatform@ + -> Version + -- ^ GHC version (@cProjectVersion@ is your friend) + -> IO (Maybe FilePath) +getSandboxPkgDb readProc = + CabalHelper.Shared.Sandbox.getSandboxPkgDb $ unsafePerformIO $ buildPlatform readProc + +buildPlatform :: (FilePath -> [String] -> String -> IO String) -> IO String +buildPlatform readProc = do + exe <- findLibexecExe + CabalHelper.Shared.Sandbox.dropWhileEnd isSpace <$> readProc exe ["print-build-platform"] "" + +-- | This exception is thrown by all 'runQuery' functions if the internal +-- wrapper executable cannot be found. You may catch this and present the user +-- an appropriate error message however the default is to print +-- 'libexecNotFoundError'. +data LibexecNotFoundError = LibexecNotFoundError String FilePath + deriving (Typeable) +instance Exception LibexecNotFoundError +instance Show LibexecNotFoundError where + show (LibexecNotFoundError exe dir) = + libexecNotFoundError exe dir "https://github.com/DanielG/cabal-helper/issues" + +findLibexecExe :: IO FilePath +findLibexecExe = do + libexecdir <- getLibexecDir + let exeName = "cabal-helper-wrapper" + exe = libexecdir exeName FP.<.> exeExtension' + + exists <- doesFileExist exe + + if exists + then return exe + else do + mdir <- tryFindCabalHelperTreeLibexecDir + case mdir of + Nothing -> + error $ throw $ LibexecNotFoundError exeName libexecdir + Just dir -> + return $ dir "dist" "build" exeName exeName + +tryFindCabalHelperTreeLibexecDir :: IO (Maybe FilePath) +tryFindCabalHelperTreeLibexecDir = do + exe <- getExecutablePath' + dir <- case takeFileName exe of + "ghc" -> do -- we're probably in ghci; try CWD + getCurrentDirectory + _ -> + return $ (!!4) $ iterate takeDirectory exe + exists <- doesFileExist $ dir "cabal-helper.cabal" + return $ if exists + then Just dir + else Nothing + +libexecNotFoundError :: String -- ^ Name of the executable we were trying to + -- find + -> FilePath -- ^ Path to @$libexecdir@ + -> String -- ^ URL the user will be directed towards to + -- report a bug. + -> String +libexecNotFoundError exe dir reportBug = printf + ( "Could not find $libexecdir/%s\n" + ++"\n" + ++"If you are a cabal-helper developer you can set the environment variable\n" + ++"`cabal_helper_libexecdir' to override $libexecdir[1]. The following will\n" + ++"work in the cabal-helper source tree:\n" + ++"\n" + ++" $ export cabal_helper_libexecdir=$PWD/dist/build/%s\n" + ++"\n" + ++"[1]: %s\n" + ++"\n" + ++"If you don't know what I'm talking about something went wrong with your\n" + ++"installation. Please report this problem here:\n" + ++"\n" + ++" %s") exe exe dir reportBug + +getExecutablePath' :: IO FilePath +getExecutablePath' = +#if MIN_VERSION_base(4,6,0) + getExecutablePath +#else + getProgName +#endif + +lookupEnv' :: String -> IO (Maybe String) +lookupEnv' k = lookup k <$> getEnvironment + +exeExtension' :: FilePath +exeExtension' = Distribution.Simple.BuildPaths.exeExtension diff --git a/src/CabalHelper/Compiletime/Compat/Environment.hs b/src/CabalHelper/Compiletime/Compat/Environment.hs new file mode 100644 index 0000000..916f782 --- /dev/null +++ b/src/CabalHelper/Compiletime/Compat/Environment.hs @@ -0,0 +1,6 @@ +module CabalHelper.Compiletime.Compat.Environment where + +import System.Environment + +lookupEnv :: String -> IO (Maybe String) +lookupEnv var = do env <- getEnvironment; return (lookup var env) diff --git a/src/CabalHelper/Compiletime/Compat/Version.hs b/src/CabalHelper/Compiletime/Compat/Version.hs new file mode 100644 index 0000000..853aca5 --- /dev/null +++ b/src/CabalHelper/Compiletime/Compat/Version.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE CPP #-} +module CabalHelper.Compiletime.Compat.Version + ( DataVersion + , toDataVersion + , fromDataVersion + , Data.Version.showVersion + ) 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 diff --git a/src/CabalHelper/Compiletime/Compile.hs b/src/CabalHelper/Compiletime/Compile.hs new file mode 100644 index 0000000..8cc565e --- /dev/null +++ b/src/CabalHelper/Compiletime/Compile.hs @@ -0,0 +1,595 @@ +-- 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 Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . +{-# LANGUAGE RecordWildCards, FlexibleContexts #-} + +{-| +Module : CabalHelper.Compiletime.Compile +Description : Runtime compilation machinery +License : AGPL-3 +-} + +module CabalHelper.Compiletime.Compile where + +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.Traversable +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 System.Directory +import System.FilePath +import System.Process +import System.Exit +import System.IO +import System.IO.Error +import System.IO.Temp +import Prelude + +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 = Compile { + compCabalSourceDir :: Maybe CabalSourceDir, + compPackageDb :: Maybe PackageDbDir, + compCabalVersion :: Either String Version, + compPackageDeps :: [String] + } + +compileHelper :: Options -> Version -> FilePath -> FilePath -> IO (Either ExitCode FilePath) +compileHelper opts cabalVer projdir distdir = do + case cabalPkgDb opts of + Nothing -> + run [ compileCabalSource + , Right <$> MaybeT (cachedExe cabalVer) + , compileSandbox + , compileGlobal + , cachedCabalPkg + , MaybeT (Just <$> compilePrivatePkgDb) + ] + mdb -> + run [ Right <$> MaybeT (cachedExe cabalVer) + , liftIO $ compileWithPkg mdb cabalVer + ] + + where + run actions = fromJust <$> runMaybeT (msum actions) + + logMsg = "compiling helper with Cabal from " + +-- for relaxed deps: find (sameMajorVersionAs cabalVer) . reverse . sort + + -- | Check if this version is globally available + compileGlobal :: MaybeT IO (Either ExitCode FilePath) + compileGlobal = do + ver <- MaybeT $ find (== cabalVer) <$> listCabalVersions opts + vLog opts $ logMsg ++ "user/global package-db" + liftIO $ compileWithPkg Nothing ver + + -- | Check if this version is available in the project sandbox + compileSandbox :: MaybeT IO (Either ExitCode FilePath) + compileSandbox = do + let ghcVer = ghcVersion opts + mdb_path = getSandboxPkgDb projdir (display buildPlatform) =<< ghcVer + sandbox <- PackageDbDir <$> MaybeT mdb_path + ver <- MaybeT $ logIOError opts "compileSandbox" $ + find (== cabalVer) <$> listCabalVersions' opts (Just sandbox) + vLog opts $ logMsg ++ "sandbox package-db" + liftIO $ compileWithPkg (Just sandbox) ver + + + -- | Check if we already compiled this version of cabal into a private + -- package-db + cachedCabalPkg :: MaybeT IO (Either ExitCode FilePath) + cachedCabalPkg = do + db_exists <- liftIO $ cabalVersionExistsInPkgDb opts cabalVer + case db_exists of + False -> mzero + True -> do + db@(PackageDbDir db_path) + <- liftIO $ getPrivateCabalPkgDb opts (Right cabalVer) + vLog opts $ logMsg ++ "private package-db in " ++ db_path + liftIO $ compileWithPkg (Just db) cabalVer + + -- | See if we're in a cabal source tree + compileCabalSource :: MaybeT IO (Either ExitCode FilePath) + compileCabalSource = do + let cabalFile = projdir "Cabal.cabal" + cabalSrc <- liftIO $ doesFileExist cabalFile + let projdir' = CabalSourceDir projdir + case cabalSrc of + False -> mzero + True -> liftIO $ do + vLog opts $ "directory above distdir looks like cabal source tree (Cabal.cabal exists)" + ver <- cabalFileVersion <$> readFile cabalFile + vLog opts $ "compiling helper with local Cabal source tree" + compileWithCabalTree ver projdir' + + -- | Compile the requested cabal version into an isolated package-db + compilePrivatePkgDb :: IO (Either ExitCode FilePath) + compilePrivatePkgDb = do + db <- fst <$> installCabal opts (Right cabalVer) `E.catch` + \(SomeException _) -> errorInstallCabal cabalVer distdir + compileWithPkg (Just db) cabalVer + + compileWithCabalTree ver srcDir = + compile distdir opts $ Compile { + compCabalSourceDir = Just srcDir, + compPackageDb = Nothing, + compCabalVersion = Right ver, + compPackageDeps = [] + } + + compileWithPkg mdb ver = + compile distdir opts $ Compile { + compCabalSourceDir = Nothing, + compPackageDb = mdb, + compCabalVersion = Right ver, + compPackageDeps = [cabalPkgId ver] + } + + cabalPkgId v = "Cabal-" ++ showVersion v + +compile :: FilePath -> Options -> Compile -> IO (Either ExitCode FilePath) +compile distdir opts@Options {..} Compile {..} = do + cnCabalSourceDir + <- (canonicalizePath . cabalSourceDir) `traverse` compCabalSourceDir + appdir <- appCacheDir + + let (outdir, exedir, exe, mchsrcdir) = + case cnCabalSourceDir of + Nothing -> ( exeName compCabalVersion <.> "build" + , appdir + , appdir exeName compCabalVersion + , Nothing + ) + Just _ -> ( distdir "cabal-helper" + , distdir + , distdir "cabal-helper" "cabal-helper" + , Just $ distdir "cabal-helper" + ) + + createDirectoryIfMissing True outdir + createDirectoryIfMissing True exedir + + withHelperSources mchsrcdir $ \compCabalHelperSourceDir -> do + + vLog opts $ "sourcedir: " ++ compCabalHelperSourceDir + vLog opts $ "outdir: " ++ outdir + vLog opts $ "exe: " ++ exe + + let (mj1:mj2:mi:_) = case compCabalVersion of + Left _commitid -> [10000000, 0, 0] + Right (Version vs _) -> vs + let ghc_opts = concat [ + [ "-outputdir", outdir + , "-o", exe + , "-optP-DCABAL_HELPER=1" + , "-optP-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++")" + ], + maybeToList $ ("-package-conf="++) <$> packageDbDir <$> compPackageDb, + map ("-i"++) $ nub $ "":compCabalHelperSourceDir:maybeToList cnCabalSourceDir, + + if isNothing cnCabalSourceDir + then [ "-hide-all-packages" + , "-package", "base" + , "-package", "containers" + , "-package", "directory" + , "-package", "filepath" + , "-package", "process" + , "-package", "bytestring" + , "-package", "ghc-prim" + ] + else [], + + concatMap (\p -> ["-package", p]) compPackageDeps, + [ "--make" + , compCabalHelperSourceDir"CabalHelper""Runtime""Main.hs" + ] + ] + + rv <- callProcessStderr' opts Nothing ghcProgram ghc_opts + return $ case rv of + ExitSuccess -> Right exe + e@(ExitFailure _) -> Left e + +exeName :: Either String Version -> String +exeName (Left commitid) = intercalate "-" + [ "cabal-helper" ++ showVersion version -- our ver + , "CabalHEAD" ++ commitid + ] +exeName (Right compCabalVersion) = intercalate "-" + [ "cabal-helper" ++ showVersion version -- our ver + , "Cabal" ++ showVersion compCabalVersion + ] + +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, Either String Version) +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, e_commit_ver) <- case ever of + Left HEAD -> do + second Left <$> unpackCabalHEAD tmpdir + Right ver -> do + message ver + let patch = fromMaybe nopCabalPatchDescription $ + find ((ver`elem`) . cpdVersions) patchyCabalVersions + (,) <$> unpackPatchedCabal opts ver tmpdir patch <*> pure (Right ver) + + db <- createPkgDb opts e_commit_ver + + runCabalInstall opts db srcdir ever + + return (db, e_commit_ver) + +{- +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 + cabalInstallVer <- cabalInstallVersion opts + cabal_opts <- return $ concat + [ + [ "--package-db=clear" + , "--package-db=global" + , "--package-db=" ++ db + , "--prefix=" ++ db "prefix" + ] + , cabalOptions opts + , if cabalInstallVer >= Version [1,20,0,0] [] + then ["--no-require-sandbox"] + else [] + , [ "install", srcdir ] + , if verbose opts + then ["-v"] + else [] + , [ "--only-dependencies" ] + ] + + callProcessStderr opts (Just "/") (cabalProgram opts) cabal_opts + + setupProgram <- compileSetupHs opts db srcdir + runSetupHs opts setupProgram db srcdir ever + + hPutStrLn stderr "done" + +cabalOptions :: Options -> [String] +cabalOptions opts = + concat [ [ "--with-ghc=" ++ ghcProgram opts ] + , if ghcPkgProgram opts /= ghcPkgProgram defaultOptions + then [ "--with-ghc-pkg=" ++ ghcPkgProgram opts ] + else [] + ] + +runSetupHs + :: Options + -> SetupProgram + -> FilePath + -> FilePath + -> Either HEAD Version + -> IO () +runSetupHs opts SetupProgram {..} db srcdir ever = do + let run = callProcessStderr opts (Just srcdir) setupProgram + parmake_opt + | Right ver <- ever, ver >= Version [1,20] [] = ["-j"] + | otherwise = [] + + run $ [ "configure", "--package-db", db, "--prefix", db "prefix" ] ++ cabalOptions opts + run $ [ "build" ] ++ parmake_opt + 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) (ghcProgram 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 { cabalSourceDir :: 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) (cabalProgram opts) args + return $ CabalSourceDir dir + +unpackCabalHEAD :: FilePath -> IO (CabalSourceDir, String) +unpackCabalHEAD 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 "git" ["rev-parse", "HEAD"] "" + return (CabalSourceDir $ dir "Cabal", 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 + +cachedExe :: Version -> IO (Maybe FilePath) +cachedExe compCabalVersion = do + appdir <- appCacheDir + let exe = appdir exeName (Right compCabalVersion) + exists <- doesFileExist exe + return $ if exists then Just exe else Nothing + +listCabalVersions :: Options -> IO [Version] +listCabalVersions opts = listCabalVersions' opts Nothing + +-- TODO: Include sandbox? Probably only relevant for build-type:custom projects. +listCabalVersions' :: Options -> Maybe PackageDbDir -> IO [Version] +listCabalVersions' Options {..} mdb = do + let mdbopt = ("--package-conf="++) <$> packageDbDir <$> mdb + opts = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt + + catMaybes . map (fmap snd . parsePkgId . fromString) . words + <$> readProcess ghcPkgProgram opts "" + +cabalVersionExistsInPkgDb :: Options -> Version -> IO Bool +cabalVersionExistsInPkgDb opts cabalVer = do + db@(PackageDbDir db_path) <- getPrivateCabalPkgDb opts (Right cabalVer) + exists <- doesDirectoryExist db_path + case exists of + False -> return False + True -> do + vers <- listCabalVersions' opts (Just db) + return $ cabalVer `elem` vers + + +ghcVersion :: Options -> IO Version +ghcVersion Options {..} = do + parseVer . trim <$> readProcess ghcProgram ["--numeric-version"] "" + +ghcPkgVersion :: Options -> IO Version +ghcPkgVersion Options {..} = do + parseVer . trim . dropWhile (not . isDigit) <$> readProcess ghcPkgProgram ["--version"] "" + +cabalInstallVersion :: Options -> IO Version +cabalInstallVersion Options {..} = do + parseVer . trim <$> readProcess cabalProgram ["--numeric-version"] "" + +trim :: String -> String +trim = dropWhileEnd isSpace + +createPkgDb :: Options -> Either String Version -> IO PackageDbDir +createPkgDb opts@Options {..} cabalVer = do + db@(PackageDbDir db_path) <- getPrivateCabalPkgDb opts cabalVer + exists <- doesDirectoryExist db_path + when (not exists) $ callProcessStderr opts Nothing ghcPkgProgram ["init", db_path] + return db + +getPrivateCabalPkgDb :: Options -> Either String Version -> 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 cabalFile = + fromJust $ parseVer . extract <$> find ("version:" `isPrefixOf`) ls + where + ls = map (map toLower) $ lines cabalFile + extract = dropWhile (/=':') >>> drop 1 >>> dropWhile isSpace >>> takeWhile (not . isSpace) diff --git a/src/CabalHelper/Compiletime/Data.hs b/src/CabalHelper/Compiletime/Data.hs new file mode 100644 index 0000000..dce3570 --- /dev/null +++ b/src/CabalHelper/Compiletime/Data.hs @@ -0,0 +1,86 @@ +-- 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 Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero 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 : AGPL-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.Posix.Files +import System.Posix.Time +import System.Posix.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 + +withHelperSources :: Maybe FilePath -> (FilePath -> IO a) -> IO a +withHelperSources mdir action = withDir mdir $ \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 + + action dir + where + withDir (Just dir) = \f -> f dir + withDir Nothing = withSystemTempDirectoryEnv "cabal-helper-source" + + +sourceFiles :: [(FilePath, String)] +sourceFiles = + [ ("Runtime/Main.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Runtime/Main.hs"))) + , ("Runtime/Licenses.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "src/CabalHelper/Runtime/Licenses.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/src/CabalHelper/Compiletime/GuessGhc.hs b/src/CabalHelper/Compiletime/GuessGhc.hs new file mode 100644 index 0000000..f4b33d5 --- /dev/null +++ b/src/CabalHelper/Compiletime/GuessGhc.hs @@ -0,0 +1,92 @@ +-- Copyright (c) 2003-2014, Isaac Jones, Simon Marlow, Martin Sjögren, +-- Bjorn Bringert, Krasimir Angelov, +-- Malcolm Wallace, Ross Patterson, Ian Lynagh, +-- Duncan Coutts, Thomas Schilling, +-- Johan Tibell, Mikhail Glushenkov +-- All rights reserved. + +-- Redistribution and use in source and binary forms, with or without +-- modification, are permitted provided that the following conditions are +-- met: + +-- * Redistributions of source code must retain the above copyright +-- notice, this list of conditions and the following disclaimer. + +-- * Redistributions in binary form must reproduce the above +-- copyright notice, this list of conditions and the following +-- disclaimer in the documentation and/or other materials provided +-- with the distribution. + +-- * Neither the name of Isaac Jones nor the names of other +-- contributors may be used to endorse or promote products derived +-- from this software without specific prior written permission. + +-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT +-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR +-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT +-- OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, +-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT +-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, +-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY +-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT +-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. + +{-| +Module : CabalHelper.Compiletime.GuessGhc +Description : Logic for finding @ghc-pkg@ based on path to @ghc@ +License : BSD3 +-} + +module CabalHelper.Compiletime.GuessGhc (guessToolFromGhcPath) where + +import Data.Maybe +import Data.Char +import Distribution.Simple.BuildPaths +import System.Directory +import System.FilePath + +guessToolFromGhcPath :: FilePath -- ^ Tool name + -> FilePath -- ^ GHC exe path + -> IO (Maybe FilePath) +guessToolFromGhcPath toolname ghcPath + = do let + path = ghcPath + dir = takeDirectory path + versionSuffix = takeVersionSuffix (dropExeExtension path) + guessNormal = dir toolname <.> exeExtension' + guessGhcVersioned = dir (toolname ++ "-ghc" ++ versionSuffix) + <.> exeExtension' + guessVersioned = dir (toolname ++ versionSuffix) + <.> exeExtension' + guesses | null versionSuffix = [guessNormal] + | otherwise = [guessGhcVersioned, + guessVersioned, + guessNormal] + exists <- mapM doesFileExist guesses + return $ listToMaybe [ file | (file, True) <- zip guesses exists ] + + where takeVersionSuffix :: FilePath -> String + takeVersionSuffix = takeWhileEndLE isSuffixChar + + isSuffixChar :: Char -> Bool + isSuffixChar c = isDigit c || c == '.' || c == '-' + + dropExeExtension :: FilePath -> FilePath + dropExeExtension filepath = + case splitExtension filepath of + (filepath', extension) | extension == exeExtension' -> filepath' + | otherwise -> filepath + +-- | @takeWhileEndLE p@ is equivalent to @reverse . takeWhile p . reverse@, but +-- is usually faster (as well as being easier to read). +takeWhileEndLE :: (a -> Bool) -> [a] -> [a] +takeWhileEndLE p = fst . foldr go ([], False) + where + go x (rest, done) + | not done && p x = (x:rest, False) + | otherwise = (rest, True) + +exeExtension' :: FilePath +exeExtension' = Distribution.Simple.BuildPaths.exeExtension diff --git a/src/CabalHelper/Compiletime/Log.hs b/src/CabalHelper/Compiletime/Log.hs new file mode 100644 index 0000000..a75f8b7 --- /dev/null +++ b/src/CabalHelper/Compiletime/Log.hs @@ -0,0 +1,44 @@ +-- 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 Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-# LANGUAGE ScopedTypeVariables #-} + +{-| +Module : CabalHelper.Compiletime.Log +Description : Basic logging facilities +License : AGPL-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 { verbose = 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/src/CabalHelper/Compiletime/Types.hs b/src/CabalHelper/Compiletime/Types.hs new file mode 100644 index 0000000..bfe9b7c --- /dev/null +++ b/src/CabalHelper/Compiletime/Types.hs @@ -0,0 +1,40 @@ +-- Copyright (C) 2015 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DefaultSignatures #-} + +{-| +Module : CabalHelper.Compiletime.Types +Description : Types used throughout +License : AGPL-3 +-} + +module CabalHelper.Compiletime.Types where + +import Data.Version + +data Options = Options { + verbose :: Bool + , ghcProgram :: FilePath + , ghcPkgProgram :: FilePath + , cabalProgram :: FilePath + , cabalVersion :: Maybe Version + , cabalPkgDb :: Maybe PackageDbDir +} + +newtype PackageDbDir = PackageDbDir { packageDbDir :: FilePath } + +defaultOptions :: Options +defaultOptions = Options False "ghc" "ghc-pkg" "cabal" Nothing Nothing diff --git a/src/CabalHelper/Compiletime/Wrapper.hs b/src/CabalHelper/Compiletime/Wrapper.hs new file mode 100644 index 0000000..6713944 --- /dev/null +++ b/src/CabalHelper/Compiletime/Wrapper.hs @@ -0,0 +1,164 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . +{-# LANGUAGE RecordWildCards, FlexibleContexts #-} +module Main where + +import Control.Applicative +import Control.Monad +import Data.Char +import Data.List +import Data.Maybe +import Data.String +import Text.Printf +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 Distribution.System (buildPlatform) +import Distribution.Text (display) +import Distribution.Verbosity (silent, deafening) +import Distribution.PackageDescription.Parse (readPackageDescription) +import Distribution.Package (packageName, packageVersion) + +import Paths_cabal_helper (version) +import CabalHelper.Compiletime.Compat.Version +import CabalHelper.Compiletime.Compile +import CabalHelper.Compiletime.GuessGhc +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\ +\ PROJ_DIR DIST_DIR ( print-exe | package-id | [CABAL_HELPER_ARGS...] ) )\n" + +globalArgSpec :: [OptDescr (Options -> Options)] +globalArgSpec = + [ option "" ["verbose"] "Be more verbose" $ + NoArg $ \o -> o { verbose = True } + + , option "" ["with-ghc"] "GHC executable to use" $ + reqArg "PROG" $ \p o -> o { ghcProgram = p } + + , option "" ["with-ghc-pkg"] "ghc-pkg executable to use (only needed when guessing from GHC path fails)" $ + reqArg "PROG" $ \p o -> o { ghcPkgProgram = p } + + , option "" ["with-cabal"] "cabal-install executable to use" $ + reqArg "PROG" $ \p o -> o { cabalProgram = p } + + , option "" ["with-cabal-version"] "Cabal library version to use" $ + reqArg "VERSION" $ \p o -> o { cabalVersion = Just $ parseVer p } + + , option "" ["with-cabal-pkg-db"] "package database to look for Cabal library in" $ + reqArg "PKG_DB" $ \p o -> o { cabalPkgDb = 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 + if not (same ghcProgram opts dopts) && same ghcPkgProgram opts dopts + then do + mghcPkg <- guessToolFromGhcPath "ghc-pkg" (ghcProgram opts) + return opts { + ghcPkgProgram = fromMaybe (ghcPkgProgram opts) mghcPkg + } + else return opts + 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 { verbose = True } + Nothing -> opts + +main :: IO () +main = handlePanic $ do + (opts', args) <- parseCommandArgs defaultOptions <$> getArgs + opts <- overrideVerbosityEnvVar =<< guessProgramPaths opts' + case args of + [] -> 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 | verbose 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)] + + projdir:distdir:args' -> do + cfgf <- canonicalizePath (distdir "setup-config") + mhdr <- getCabalConfigHeader cfgf + case mhdr 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, _) -> do + case cabalVersion opts of + Just ver | hdrCabalVersion /= ver -> panic $ printf "\ +\Cabal version %s was requested but setup configuration was\n\ +\written by version %s" (showVersion ver) (showVersion hdrCabalVersion) + _ -> do + eexe <- compileHelper opts hdrCabalVersion projdir distdir + case eexe of + Left e -> exitWith e + Right exe -> + case args' of + "print-exe":_ -> putStrLn exe + _ -> do + (_,_,_,h) <- createProcess $ proc exe args + exitWith =<< waitForProcess h + _ -> error "invalid command line" diff --git a/src/CabalHelper/Runtime/Licenses.hs b/src/CabalHelper/Runtime/Licenses.hs new file mode 100644 index 0000000..a1794ea --- /dev/null +++ b/src/CabalHelper/Runtime/Licenses.hs @@ -0,0 +1,125 @@ +{-# LANGUAGE CPP #-} + +#ifdef MIN_VERSION_Cabal +#undef CH_MIN_VERSION_Cabal +#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal +#endif + +module CabalHelper.Runtime.Licenses ( + displayDependencyLicenseList + , groupByLicense + , getDependencyInstalledPackageInfos + ) where + +-- Copyright (c) 2014, Jasper Van der Jeugt + +-------------------------------------------------------------------------------- +import Control.Arrow ((***), (&&&)) +import Control.Monad (forM_, unless) +import Data.List (foldl', sort) +import Data.Maybe (catMaybes) +import Data.Set (Set) +import qualified Data.Set as Set +import System.Directory (getDirectoryContents) +import System.Exit (exitFailure) +import System.FilePath (takeExtension) +import System.IO (hPutStrLn, stderr) + +import Distribution.InstalledPackageInfo +import Distribution.License +import Distribution.Package +import Distribution.Simple.Configure +import Distribution.Simple.LocalBuildInfo +import Distribution.Simple.PackageIndex +import Distribution.Text +import Distribution.ModuleName +import Distribution.Version (Version) +-------------------------------------------------------------------------------- + + + +#if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP > 1.22 +type CPackageIndex a = PackageIndex (InstalledPackageInfo) +#elif CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 +type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a) +#else +type CPackageIndex a = PackageIndex +#endif + +#if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP >= 1.23 +type CInstalledPackageId = UnitId +lookupInstalledPackageId' :: PackageIndex a -> UnitId -> Maybe a +lookupInstalledPackageId' = lookupUnitId +#else +type CInstalledPackageId = InstalledPackageId +lookupInstalledPackageId' = lookupInstalledPackageId +#endif + +findTransitiveDependencies + :: CPackageIndex Distribution.ModuleName.ModuleName + -> Set CInstalledPackageId + -> Set CInstalledPackageId +findTransitiveDependencies pkgIdx set0 = go Set.empty (Set.toList set0) + where + go set [] = set + go set (q : queue) + | q `Set.member` set = go set queue + | otherwise = + case lookupInstalledPackageId' pkgIdx q of + Nothing -> + -- Not found can mean that the package still needs to be + -- installed (e.g. a component of the target cabal package). + -- We can ignore those. + go set queue + Just ipi -> + go (Set.insert q set) (Distribution.InstalledPackageInfo.depends ipi ++ queue) + + +-------------------------------------------------------------------------------- +getDependencyInstalledPackageIds + :: LocalBuildInfo -> Set CInstalledPackageId +getDependencyInstalledPackageIds lbi = + findTransitiveDependencies (installedPkgs lbi) $ + Set.fromList $ map fst $ externalPackageDeps lbi + +-------------------------------------------------------------------------------- +getDependencyInstalledPackageInfos + :: LocalBuildInfo -> [InstalledPackageInfo] +getDependencyInstalledPackageInfos lbi = catMaybes $ + map (lookupInstalledPackageId' pkgIdx) $ + Set.toList (getDependencyInstalledPackageIds lbi) + where + pkgIdx = installedPkgs lbi + + +-------------------------------------------------------------------------------- +groupByLicense + :: [InstalledPackageInfo] + -> [(License, [InstalledPackageInfo])] +groupByLicense = foldl' + (\assoc ipi -> insertAList (license ipi) ipi assoc) [] + where + -- 'Cabal.License' doesn't have an 'Ord' instance so we need to use an + -- association list instead of 'Map'. The number of licenses probably won't + -- exceed 100 so I think we're alright. + insertAList :: Eq k => k -> v -> [(k, [v])] -> [(k, [v])] + insertAList k v [] = [(k, [v])] + insertAList k v ((k', vs) : kvs) + | k == k' = (k, v : vs) : kvs + | otherwise = (k', vs) : insertAList k v kvs + + +-------------------------------------------------------------------------------- +displayDependencyLicenseList + :: [(License, [InstalledPackageInfo])] + -> [(String, [(String, Version)])] +displayDependencyLicenseList = + map (display *** map (getName &&& getVersion)) + where + getName = + display . pkgName . sourcePackageId + getVersion = + pkgVersion . sourcePackageId diff --git a/src/CabalHelper/Runtime/Main.hs b/src/CabalHelper/Runtime/Main.hs new file mode 100644 index 0000000..86bf169 --- /dev/null +++ b/src/CabalHelper/Runtime/Main.hs @@ -0,0 +1,539 @@ +-- Copyright (C) 2015 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-# LANGUAGE CPP, BangPatterns, RecordWildCards, RankNTypes, ViewPatterns #-} +{-# OPTIONS_GHC -fno-warn-deprecations #-} + +#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) +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP CABAL_MAJOR == 1 && CABAL_MINOR >= 25 +import Distribution.PackageDescription (unFlagName, mkFlagName) +#endif +import Distribution.PackageDescription.Parse (readPackageDescription) +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) +#if CH_MIN_VERSION_Cabal(1,23,0) +-- >= 1.23 +import Distribution.Simple.LocalBuildInfo (localUnitId) +#else +-- <= 1.22 +import Distribution.Simple.LocalBuildInfo (inplacePackageId) +#endif + +import Distribution.Simple.GHC (componentGhcOptions) +import Distribution.Simple.Program.GHC (GhcOptions(..), renderGhcOptions) + +import Distribution.Simple.Setup (ConfigFlags(..),Flag(..)) +import Distribution.Simple.Build (initialBuildSteps) +import Distribution.Simple.BuildPaths (autogenModuleName, cppHeaderName, exeExtension) +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(2,0,0) +-- CPP >= 2.0 +import Distribution.Version (versionNumbers, mkVersion) +#endif + +#if CH_MIN_VERSION_Cabal(1,22,0) +-- CPP >= 1.22 +import Distribution.Utils.NubList +#endif + +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 +import Distribution.Types.ForeignLib (ForeignLib(..)) +import Distribution.Types.UnqualComponentName (unUnqualComponentName) +#endif + +#if CH_MIN_VERSION_Cabal(2,0,0) +import Distribution.Types.UnitId (UnitId) +import Distribution.Types.MungedPackageId (MungedPackageId) +#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 + +import CabalHelper.Runtime.Licenses + +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" + ++" | source-dirs\n" + ++" | licenses\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" + , "source-dirs" + , "licenses"] + +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 $$ \cmd -> do + case cmd of + "flags":[] -> do + return $ Just $ ChResponseFlags $ sort $ + map (flagName' &&& flagDefault) $ genPackageFlags gpd + + "config-flags":[] -> do + return $ Just $ ChResponseFlags $ sort $ + map (first unFlagName) $ configConfigurationsFlags $ configFlags lbi + + "non-default-config-flags":[] -> do + let flagDefinitons = genPackageFlags gpd + flagAssgnments = configConfigurationsFlags $ configFlags lbi + nonDefaultFlags = + [ (fn, v) + | MkFlag {flagName=(unFlagName -> fn), flagDefault=dv} <- flagDefinitons + , (unFlagName -> fn', v) <- flagAssgnments + , fn == fn' + , v /= dv + ] + 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 + let pd = localPkgDescr lbi + 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 + eps <- componentsMap lbi v distdir $ \c clbi bi -> + return $ componentEntrypoints c + -- MUST append Setup component at the end otherwise CabalHelper gets + -- confused + let eps' = eps ++ [(ChSetupHsName, ChSetupEntrypoint)] + return $ Just $ ChResponseEntrypoints eps' + + "source-dirs":[] -> do + res <- componentsMap lbi v distdir $$ \_ _ bi -> return $ hsSourceDirs bi + return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) + + "licenses":[] -> do + return $ Just $ ChResponseLicenses $ + map (second (map (second toDataVersion))) $ + displayDependencyLicenseList $ + groupByLicense $ getDependencyInstalledPackageInfos lbi + + "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 + +#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 + +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 + + +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 + writeIORef lr $ (componentNameToCh name, r):l' + + reverse <$> readIORef lr + +componentOptions' (lbi, v, distdir) inplaceFlag flags rf f = do + let pd = localPkgDescr lbi + 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) + [] -> removeInplaceDeps v lbi pd clbi + 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 + +componentNameToCh CLibName = ChLibName +#if CH_MIN_VERSION_Cabal(1,25,0) +-- CPP >= 1.25 +componentNameToCh (CSubLibName n) = ChSubLibName $ unUnqualComponentName' n +componentNameToCh (CFLibName n) = ChFLibName $ unUnqualComponentName' n +#endif +componentNameToCh (CExeName n) = ChExeName $ unUnqualComponentName' n +componentNameToCh (CTestName n) = ChTestName $ unUnqualComponentName' n +componentNameToCh (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 +componentOutDir lbi (CExe Executable {..})= exeOutDir lbi (unUnqualComponentName' exeName) +componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteExeV10 _ _, ..}) = + exeOutDir lbi (unUnqualComponentName' testName) +componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteLibV09 _ _, ..}) = + exeOutDir lbi (unUnqualComponentName' testName ++ "Stub") +componentOutDir lbi (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ _, ..})= + exeOutDir lbi (unUnqualComponentName' benchmarkName) + +gmModuleName :: C.ModuleName -> ChModuleName +gmModuleName = ChModuleName . intercalate "." . components + +componentEntrypoints :: Component -> ChEntrypoint +componentEntrypoints (CLib Library {..}) + = ChLibEntrypoint + (map gmModuleName exposedModules) + (map gmModuleName $ otherModules libBuildInfo) +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 [] [] + +exeOutDir :: LocalBuildInfo -> String -> FilePath +exeOutDir lbi exeName' = + ----- Copied from Distribution/Simple/GHC.hs:buildOrReplExe + let targetDir = (buildDir lbi) exeName' + exeDir = targetDir (exeName' ++ "-tmp") + in exeDir + + +removeInplaceDeps :: Verbosity + -> LocalBuildInfo + -> PackageDescription + -> ComponentLocalBuildInfo + -> (ComponentLocalBuildInfo, GhcOptions) +removeInplaceDeps v lbi pd clbi = let + (ideps, deps) = partition isInplaceDep (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) + + where +#if CH_MIN_VERSION_Cabal(2,0,0) + isInplaceDep :: (UnitId, MungedPackageId) -> Bool + isInplaceDep (mpid, pid) = localUnitId lbi == mpid +#else + isInplaceDep :: (InstalledPackageId, PackageId) -> Bool +# if CH_MIN_VERSION_Cabal(1,23,0) +-- CPP >= 1.23 + isInplaceDep (ipid, pid) = localUnitId lbi == ipid +# else +-- CPP <= 1.22 + isInplaceDep (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] +renderGhcOptions' lbi v opts = do +#if !CH_MIN_VERSION_Cabal(1,20,0) +-- 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) +-- CPP >= 1.20 && < 1.24 + return $ renderGhcOptions (compiler lbi) opts +#else +-- CPP >= 1.24 + return $ renderGhcOptions (compiler lbi) (hostPlatform lbi) opts +#endif + +initialBuildStepsForAllComponents distdir pd lbi v = + initialBuildSteps distdir pd lbi v diff --git a/src/CabalHelper/Shared/Common.hs b/src/CabalHelper/Shared/Common.hs new file mode 100644 index 0000000..239fe3c --- /dev/null +++ b/src/CabalHelper/Shared/Common.hs @@ -0,0 +1,128 @@ +-- Copyright (C) 2015 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-| +Module : CabalHelper.Shared.Common +Description : Shared utility functions +License : AGPL-3 +-} + +{-# LANGUAGE DeriveDataTypeable, OverloadedStrings #-} +module CabalHelper.Shared.Common where + +import Control.Applicative +import Control.Exception as E +import Control.Monad +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 +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 + +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 diff --git a/src/CabalHelper/Shared/InterfaceTypes.hs b/src/CabalHelper/Shared/InterfaceTypes.hs new file mode 100644 index 0000000..5f4972f --- /dev/null +++ b/src/CabalHelper/Shared/InterfaceTypes.hs @@ -0,0 +1,75 @@ +-- 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 Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero 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 : AGPL-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_DIR/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)] + | 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] + } + | ChExeEntrypoint { chMainIs :: FilePath + , chOtherModules :: [ChModuleName] + } deriving (Eq, Ord, Read, Show, Generic) + +data ChPkgDb = ChPkgGlobal + | ChPkgUser + | ChPkgSpecific FilePath + deriving (Eq, Ord, Read, Show, Generic) diff --git a/src/CabalHelper/Shared/Sandbox.hs b/src/CabalHelper/Shared/Sandbox.hs new file mode 100644 index 0000000..4dd9705 --- /dev/null +++ b/src/CabalHelper/Shared/Sandbox.hs @@ -0,0 +1,77 @@ +-- Copyright (C) 2015 Daniel Gröber +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero 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 Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see . + +{-| +Module : CabalHelper.Shared.Sandbox +Description : Extracting information from @cabal.sandbox.config@ files +License : AGPL-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