diff options
author | Daniel Gröber <dxld@darkboxed.org> | 2017-09-18 01:23:22 +0200 |
---|---|---|
committer | Daniel Gröber <dxld@darkboxed.org> | 2017-09-18 01:35:40 +0200 |
commit | f864a5eae8262752162c6b0d124aea4601ed9ac1 (patch) | |
tree | 1b765d25741b6e47d4ad458c8041c0881dd353b8 /CabalHelper/Compiletime | |
parent | 70d743eb6a8b7f8da182524fa0b2c4bf02399d50 (diff) |
Fix literally everything :)
Sorry for the megacommit
- Seperate modules into:
- Compiletime, modules which are only used while building the package
- Runtime, modues included in the wrapper binary to be compiled on the
users machine at runtime
- Shared, modues used in both contexts
- Refactor runtime compilation
- Completely revamp output paths
- Don't chdir when invoking ghc
- Require cabal-version 1.14 in cabal file
Diffstat (limited to 'CabalHelper/Compiletime')
-rw-r--r-- | CabalHelper/Compiletime/Compat/Version.hs | 25 | ||||
-rw-r--r-- | CabalHelper/Compiletime/Compile.hs | 502 | ||||
-rw-r--r-- | CabalHelper/Compiletime/Data.hs | 79 | ||||
-rw-r--r-- | CabalHelper/Compiletime/GuessGhc.hs | 86 | ||||
-rw-r--r-- | CabalHelper/Compiletime/Log.hs | 21 | ||||
-rw-r--r-- | CabalHelper/Compiletime/Wrapper.hs | 162 |
6 files changed, 875 insertions, 0 deletions
diff --git a/CabalHelper/Compiletime/Compat/Version.hs b/CabalHelper/Compiletime/Compat/Version.hs new file mode 100644 index 0000000..853aca5 --- /dev/null +++ b/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/CabalHelper/Compiletime/Compile.hs b/CabalHelper/Compiletime/Compile.hs new file mode 100644 index 0000000..8da3802 --- /dev/null +++ b/CabalHelper/Compiletime/Compile.hs @@ -0,0 +1,502 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015 Daniel Gröber <dxld ÄT darkboxed DOT org> +-- +-- 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 <http://www.gnu.org/licenses/>. +{-# LANGUAGE RecordWildCards, FlexibleContexts #-} +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 Text.Printf +import System.Directory +import System.FilePath +import System.Process +import System.Exit +import System.IO +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.Shared.Common +import CabalHelper.Shared.Sandbox (getSandboxPkgDb) +import CabalHelper.Shared.Types + +data Compile = Compile { + compCabalSourceDir :: Maybe FilePath, + compPackageDb :: Maybe FilePath, + 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 [ + -- TODO: here ghc's caching fails and it always recompiles, probably + -- because we write the sources to a tempdir and they always look + -- newer than the Cabal sources, not sure if we can fix this + 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 + sandbox <- MaybeT $ getSandboxPkgDb projdir (display buildPlatform) =<< ghcVersion opts + ver <- MaybeT $ logSomeError 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 $ cabalPkgDbExists opts cabalVer + case db_exists of + False -> mzero + True -> do + db <- liftIO $ getPrivateCabalPkgDb opts (Right cabalVer) + vLog opts $ logMsg ++ "private package-db in " ++ db + 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 + 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 <- installCabal opts 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 `traverse` compCabalSourceDir + appdir <- appDataDir + + 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 + + _ <- liftIO $ system $ "ls -lR " ++ compCabalHelperSourceDir + + 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="++) <$> 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" + ] + ] + + vLog opts $ intercalate " " $ map (("'"++) . (++"'")) $ ghcProgram:ghc_opts + + -- TODO: touch exe after, ghc doesn't do that if the input files didn't + -- actually change + rv <- callProcessStderr' 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' :: Maybe FilePath -> FilePath -> [String] -> IO ExitCode +callProcessStderr' mwd exe args = do + (_, _, _, h) <- createProcess (proc exe args) { std_out = UseHandle stderr + , cwd = mwd } + waitForProcess h + +callProcessStderr :: Maybe FilePath -> FilePath -> [String] -> IO () +callProcessStderr mwd exe args = do + rv <- callProcessStderr' 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 = + panic $ concat [fn, ": ", exe, " " + , intercalate " " (map show args) + , " (exit " ++ show rv ++ ")"] + +installCabal :: Options -> Version -> IO FilePath +installCabal opts ver = do + appdir <- appDataDir + 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 + let + mpatch :: Maybe (FilePath -> IO ()) + mpatch = snd <$> find ((ver`elem`) . fst) patchyCabalVersions + msrcdir <- sequenceA $ unpackPatchedCabal opts ver tmpdir <$> mpatch + db <- createPkgDb opts (Right ver) + cabalInstall opts db (maybe (Right ver) Left msrcdir) + return db + +installCabalHEAD :: Options -> IO (FilePath, String) +installCabalHEAD opts = do + withSystemTempDirectory "cabal-helper-CabalHEAD-source" $ \tmpdir -> do + (srcdir, commit) <- unpackCabalHEAD tmpdir + db <- createPkgDb opts (Left commit) + cabalInstall opts db (Left srcdir) + return (db, commit) + +cabalInstall :: Options -> FilePath -> Either FilePath Version -> IO () +cabalInstall opts db e_ver_msrcdir = do + cabalInstallVer <- cabalInstallVersion opts + cabal_opts <- return $ concat + [ + [ "--package-db=clear" + , "--package-db=global" + , "--package-db=" ++ db + , "--prefix=" ++ db </> "prefix" + , "--with-ghc=" ++ ghcProgram opts + ] + , if cabalInstallVer >= Version [1,20,0,0] [] + then ["--no-require-sandbox"] + else [] + , if ghcPkgProgram opts /= ghcPkgProgram defaultOptions + then [ "--with-ghc-pkg=" ++ ghcPkgProgram opts ] + else [] + , + case e_ver_msrcdir of + Right ver -> + [ "install", "Cabal-"++showVersion ver ] + Left srcdir -> + [ "install", srcdir ] + ] + + vLog opts $ intercalate " " + $ map (("\""++) . (++"\"")) + $ cabalProgram opts:cabal_opts + + callProcessStderr (Just "/") (cabalProgram opts) cabal_opts + hPutStrLn stderr "done" + +patchyCabalVersions :: [([Version], FilePath -> IO ())] +patchyCabalVersions = [ + ( [ Version [1,18,1] [] ] + , fixArrayConstraint + ), + + + ( [ Version [1,18,0] [] ] + , \dir -> do + fixArrayConstraint dir + fixOrphanInstance dir + ), + + -- just want the pristine version + ( [ Version [1,24,1,0] [] ] + , \_ -> return () + ) + ] + 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 -> (FilePath -> IO ()) -> IO FilePath +unpackPatchedCabal opts cabalVer tmpdir patch = do + dir <- unpackCabal opts cabalVer tmpdir + patch dir + return dir + +unpackCabal :: + Options -> Version -> FilePath -> IO FilePath +unpackCabal opts cabalVer tmpdir = do + let cabal = "Cabal-" ++ showVersion cabalVer + dir = tmpdir </> cabal + callProcessStderr (Just tmpdir) (cabalProgram opts) + [ "get", "--pristine", cabal ] + return dir + +unpackCabalHEAD :: FilePath -> IO (FilePath, 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 (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 -> a +errorInstallCabal cabalVer _distdir = panic $ 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 <- appDataDir + 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 FilePath -> IO [Version] +listCabalVersions' Options {..} mdb = do + let mdbopt = ("--package-conf="++) <$> mdb + opts = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt + + catMaybes . map (fmap snd . parsePkgId . fromString) . words + <$> readProcess ghcPkgProgram opts "" + +cabalPkgDbExists :: Options -> Version -> IO Bool +cabalPkgDbExists opts cabalVer = do + db <- getPrivateCabalPkgDb opts (Right cabalVer) + dexists <- doesDirectoryExist db + case dexists 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 FilePath +createPkgDb opts@Options {..} cabalVer = do + db <- getPrivateCabalPkgDb opts cabalVer + exists <- doesDirectoryExist db + when (not exists) $ callProcessStderr Nothing ghcPkgProgram ["init", db] + return db + +getPrivateCabalPkgDb :: Options -> Either String Version -> IO FilePath +getPrivateCabalPkgDb opts cabalVer = do + appdir <- appDataDir + ghcVer <- ghcVersion opts + return $ appdir </> exeName cabalVer ++ "-ghc" ++ showVersion ghcVer ++ ".package-db" + +-- "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 new file mode 100644 index 0000000..f04c704 --- /dev/null +++ b/CabalHelper/Compiletime/Data.hs @@ -0,0 +1,79 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015 Daniel Gröber <dxld ÄT darkboxed DOT org> +-- +-- 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 <http://www.gnu.org/licenses/>. + +{-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -fforce-recomp #-} +module CabalHelper.Compiletime.Data where + +import Control.Monad +import Control.Monad.IO.Class +import Data.Functor +import Data.Time.Clock +import Data.Time.Clock.POSIX +import qualified Data.ByteString as BS +import qualified Data.ByteString.UTF8 as UTF8 +import Language.Haskell.TH +import System.Directory +import System.Environment +import System.FilePath +import System.IO.Temp +import Prelude + +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 = read + -- See https://reproducible-builds.org/specs/source-date-epoch/ + $(runIO $ do + msde <- lookupEnv "SOURCE_DATE_EPOCH" + let parse :: String -> POSIXTime + parse = fromInteger . read + utctime <- getCurrentTime + return $ LitE . StringL $ show $ + maybe utctime (posixSecondsToUTCTime . parse) msde) + + liftIO $ forM_ sourceFiles $ \(fn, src) -> do + let path = chdir </> fn + BS.writeFile path $ UTF8.fromString src + setModificationTime path 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/Types.hs", $(LitE . StringL <$> runIO (UTF8.toString <$> BS.readFile "CabalHelper/Shared/Types.hs"))) + ] diff --git a/CabalHelper/Compiletime/GuessGhc.hs b/CabalHelper/Compiletime/GuessGhc.hs new file mode 100644 index 0000000..e1cf577 --- /dev/null +++ b/CabalHelper/Compiletime/GuessGhc.hs @@ -0,0 +1,86 @@ +module CabalHelper.Compiletime.GuessGhc (guessToolFromGhcPath) where + +import Data.Maybe +import Data.Char +import Distribution.Simple.BuildPaths +import System.Directory +import System.FilePath + +-- 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. + +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 new file mode 100644 index 0000000..e4033f1 --- /dev/null +++ b/CabalHelper/Compiletime/Log.hs @@ -0,0 +1,21 @@ +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.Shared.Types + +vLog :: MonadIO m => Options -> String -> m () +vLog Options { verbose = True } msg = + liftIO $ hPutStrLn stderr msg +vLog _ _ = return () + +logSomeError :: Options -> String -> IO (Maybe a) -> IO (Maybe a) +logSomeError opts label a = do + a `E.catch` \se@(SomeException _) -> do + vLog opts $ label ++ ": " ++ show se + return Nothing diff --git a/CabalHelper/Compiletime/Wrapper.hs b/CabalHelper/Compiletime/Wrapper.hs new file mode 100644 index 0000000..d002886 --- /dev/null +++ b/CabalHelper/Compiletime/Wrapper.hs @@ -0,0 +1,162 @@ +-- cabal-helper: Simple interface to Cabal's configuration state +-- Copyright (C) 2015 Daniel Gröber <dxld ÄT darkboxed DOT org> +-- +-- 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 <http://www.gnu.org/licenses/>. +{-# 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.Shared.Common +import CabalHelper.Shared.Types + +usage :: IO () +usage = do + prog <- getProgName + hPutStr stderr $ "Usage: " ++ prog ++ " " ++ usageMsg + where + usageMsg = "\ +\( print-appdatadir\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 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 "GHC_MOD_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 =<< appDataDir + "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 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" |