diff options
| author | Daniel Gröber <dxld@darkboxed.org> | 2018-10-22 01:20:56 +0200 | 
|---|---|---|
| committer | Daniel Gröber <dxld@darkboxed.org> | 2018-10-27 20:48:56 +0200 | 
| commit | 783eadafe6e6333123add96d2fc0276c8b4cc1d9 (patch) | |
| tree | fe16786a713d727ab5975f9b1f0f852005308053 /src/CabalHelper | |
| parent | 069225e2e61562c8166a446d201457425b91ce57 (diff) | |
Suport using Stack's built-in GHC to build the helper
Diffstat (limited to 'src/CabalHelper')
| -rw-r--r-- | src/CabalHelper/Compiletime/Compile.hs | 35 | ||||
| -rw-r--r-- | src/CabalHelper/Compiletime/Program/Stack.hs | 7 | ||||
| -rw-r--r-- | src/CabalHelper/Compiletime/Types.hs | 42 | 
3 files changed, 46 insertions, 38 deletions
| diff --git a/src/CabalHelper/Compiletime/Compile.hs b/src/CabalHelper/Compiletime/Compile.hs index 3f8a771..431043b 100644 --- a/src/CabalHelper/Compiletime/Compile.hs +++ b/src/CabalHelper/Compiletime/Compile.hs @@ -326,9 +326,10 @@ cabalMinVersionMacro (Version (mj1:mj2:mi:_) _) =  cabalMinVersionMacro _ =      error "cabalMinVersionMacro: Version must have at least 3 components" -invokeGhc :: Env => GhcInvocation -> IO (Either ExitCode FilePath) +invokeGhc +    :: (Verbose, CProgs) => GhcInvocation -> IO (Either ExitCode FilePath)  invokeGhc GhcInvocation {..} = do -    rv <- callProcessStderr' Nothing (ghcProgram ?progs) $ concat +    rv <- callProcessStderr' Nothing (ghcProgram ?cprogs) $ concat        [ [ "-outputdir", giOutDir          , "-o", giOutput          ] @@ -364,7 +365,7 @@ exeName CabalVersion {cabalVersion} = intercalate "-"      , "Cabal" ++ showVersion cabalVersion      ] -readProcess' :: Env => FilePath -> [String] -> String -> IO String +readProcess' :: Verbose => FilePath -> [String] -> String -> IO String  readProcess' exe args inp = do    vLog $ intercalate " " $ map formatProcessArg (exe:args)    outp <- readProcess exe args inp @@ -372,7 +373,7 @@ readProcess' exe args inp = do    return outp  callProcessStderr' -    :: Env => Maybe FilePath -> FilePath -> [String] -> IO ExitCode +    :: Verbose => Maybe FilePath -> FilePath -> [String] -> IO ExitCode  callProcessStderr' mwd exe args = do    let cd = case mwd of               Nothing -> []; Just wd -> [ "cd", formatProcessArg wd++";" ] @@ -381,7 +382,7 @@ callProcessStderr' mwd exe args = do                                                  , cwd = mwd }    waitForProcess h -callProcessStderr :: Env => Maybe FilePath -> FilePath -> [String] -> IO () +callProcessStderr :: Verbose => Maybe FilePath -> FilePath -> [String] -> IO ()  callProcessStderr mwd exe args = do    rv <- callProcessStderr' mwd exe args    case rv of @@ -482,9 +483,9 @@ runCabalInstall (PackageDbDir db) (CabalSourceDir srcdir) ever = do  withGHCProgramOptions :: Env => [String]  withGHCProgramOptions = -    concat [ [ "--with-ghc=" ++ oGhcProgram ] -           , if oGhcProgram /= ghcPkgProgram defaultPrograms -               then [ "--with-ghc-pkg=" ++ oGhcPkgProgram ] +    concat [ [ "--with-ghc=" ++ ghcProgram ?cprogs ] +           , if ghcProgram ?cprogs /= ghcPkgProgram defaultCompPrograms +               then [ "--with-ghc-pkg=" ++ ghcPkgProgram ?cprogs ]                 else []             ] @@ -533,7 +534,7 @@ compileSetupHs db srcdir = do        file = srcdir </> "Setup" -  callProcessStderr (Just srcdir) oGhcProgram $ concat +  callProcessStderr (Just srcdir) (ghcProgram ?cprogs) $ concat      [ [ "--make"        , "-package-conf", db        ] @@ -691,7 +692,7 @@ listCabalVersions' mdb = do                args = ["list", "--simple-output", "Cabal"] ++ maybeToList mdbopt            catMaybes . map (fmap snd . parsePkgId . fromString) . words -                   <$> readProcess' oGhcPkgProgram args "" +                   <$> readProcess' (ghcProgram ?cprogs) args ""  cabalVersionExistsInPkgDb :: Env => Version -> PackageDbDir -> IO Bool  cabalVersionExistsInPkgDb cabalVer db@(PackageDbDir db_path) = do @@ -702,14 +703,14 @@ cabalVersionExistsInPkgDb cabalVer db@(PackageDbDir db_path) = do        vers <- listCabalVersions' (Just db)        return $ cabalVer `elem` vers) -ghcVersion :: Env => IO Version +ghcVersion :: (Verbose, CProgs) => IO Version  ghcVersion = do -    parseVer . trim <$> readProcess' oGhcProgram ["--numeric-version"] "" +  parseVer . trim <$> readProcess' (ghcProgram ?cprogs) ["--numeric-version"] "" -ghcPkgVersion :: Env => IO Version +ghcPkgVersion :: (Verbose, CProgs) => IO Version  ghcPkgVersion =    parseVer . trim . dropWhile (not . isDigit) -    <$> readProcess' oGhcPkgProgram ["--version"] "" +    <$> readProcess' (ghcPkgProgram ?cprogs) ["--version"] ""  newtype CabalInstallVersion = CabalInstallVersion { cabalInstallVer :: Version }  cabalInstallVersion :: Env => IO CabalInstallVersion @@ -717,15 +718,15 @@ cabalInstallVersion = do    CabalInstallVersion . parseVer . trim      <$> readProcess' oCabalProgram ["--numeric-version"] "" -createPkgDb :: Env => CabalVersion -> IO PackageDbDir +createPkgDb :: (Verbose, CProgs) => CabalVersion -> IO PackageDbDir  createPkgDb cabalVer = do    db@(PackageDbDir db_path) <- getPrivateCabalPkgDb cabalVer    exists <- doesDirectoryExist db_path    when (not exists) $ -       callProcessStderr Nothing oGhcPkgProgram ["init", db_path] +       callProcessStderr Nothing (ghcPkgProgram ?cprogs) ["init", db_path]    return db -getPrivateCabalPkgDb :: Env => CabalVersion -> IO PackageDbDir +getPrivateCabalPkgDb :: (Verbose, CProgs) => CabalVersion -> IO PackageDbDir  getPrivateCabalPkgDb cabalVer = do    appdir <- appCacheDir    ghcVer <- ghcVersion diff --git a/src/CabalHelper/Compiletime/Program/Stack.hs b/src/CabalHelper/Compiletime/Program/Stack.hs index e7f280d..322ccaf 100644 --- a/src/CabalHelper/Compiletime/Program/Stack.hs +++ b/src/CabalHelper/Compiletime/Program/Stack.hs @@ -20,7 +20,7 @@ Description : Stack program interface  License     : GPL-3  -} -{-# LANGUAGE GADTs, DataKinds #-} +{-# LANGUAGE NamedFieldPuns, GADTs, DataKinds #-}  module CabalHelper.Compiletime.Program.Stack where @@ -64,6 +64,7 @@ projPaths qe@QueryEnv {qeProjLoc=ProjLocStackDir projdir} = do      { sppGlobalPkgDb = PackageDbDir $ look "global-pkg-db:"      , sppSnapPkgDb   = PackageDbDir $ look "snapshot-pkg-db:"      , sppLocalPkgDb  = PackageDbDir $ look "local-pkg-db:" +    , sppCompExe     = look "compiler-exe:"      }  paths :: QueryEnvI c 'Stack @@ -85,3 +86,7 @@ listPackageCabalFiles qe@QueryEnv{qeProjLoc=ProjLocStackDir projdir} = do  workdirArg :: QueryEnvI c 'Stack -> [String]  workdirArg QueryEnv{qeDistDir=DistDirStack mworkdir} =    maybeToList $ ("--work-dir="++) . unRelativePath <$> mworkdir + +patchCompPrograms :: StackProjPaths -> CompPrograms -> CompPrograms +patchCompPrograms StackProjPaths{sppCompExe} cprogs = +  cprogs { ghcProgram = sppCompExe } diff --git a/src/CabalHelper/Compiletime/Types.hs b/src/CabalHelper/Compiletime/Types.hs index cc8561f..5ae712a 100644 --- a/src/CabalHelper/Compiletime/Types.hs +++ b/src/CabalHelper/Compiletime/Types.hs @@ -101,7 +101,10 @@ data QueryEnvI cache (proj_type :: ProjType) = QueryEnv      -- processes. Useful if you need to, for example, redirect standard error      -- output away from the user\'s terminal. -    , qePrograms    :: Programs +    , qePrograms     :: !Programs +    -- ^ Field accessor for 'QueryEnv'. + +    , qeCompPrograms :: !CompPrograms      -- ^ Field accessor for 'QueryEnv'.      , qeProjLoc      :: !(ProjLoc proj_type) @@ -232,15 +235,16 @@ data StackProjPaths = StackProjPaths      { sppGlobalPkgDb :: !PackageDbDir      , sppSnapPkgDb   :: !PackageDbDir      , sppLocalPkgDb  :: !PackageDbDir +    , sppCompExe     :: !FilePath      } + +-- Beware: GHC 8.0.2 doesn't like these being recursively defined for some +-- reason so just keep them unrolled.  type Verbose = (?verbose :: Bool) -type Progs = (?progs :: Programs) --- TODO: rname to `CompEnv` or something -type Env = -    ( ?verbose :: Bool -    , ?progs   :: Programs -    ) +type Env     = (?cprogs :: CompPrograms, ?progs :: Programs, ?verbose :: Bool) +type Progs   = (?cprogs :: CompPrograms, ?progs :: Programs) +type CProgs  = (?cprogs :: CompPrograms)  -- | Configurable paths to various programs we use.  data Programs = Programs { @@ -248,21 +252,25 @@ data Programs = Programs {        cabalProgram  :: FilePath,        -- | The path to the @stack@ program. -      stackProgram  :: FilePath, +      stackProgram  :: FilePath +    } deriving (Eq, Ord, Show, Read, Generic, Typeable) -      -- | The path to the @ghc@ program. -      ghcProgram    :: FilePath, +data CompPrograms = CompPrograms +    { ghcProgram    :: FilePath +    -- ^ The path to the @ghc@ program. -      -- | The path to the @ghc-pkg@ program. If -      -- not changed it will be derived from the path to 'ghcProgram'. -      ghcPkgProgram :: FilePath +    , ghcPkgProgram :: FilePath +    -- ^ The path to the @ghc-pkg@ program. If not changed it will be derived +    -- from the path to 'ghcProgram'.      } deriving (Eq, Ord, Show, Read, Generic, Typeable)  -- | By default all programs use their unqualified names, i.e. they will be  -- searched for on @PATH@.  defaultPrograms :: Programs -defaultPrograms = Programs "cabal" "stack" "ghc" "ghc-pkg" +defaultPrograms = Programs "cabal" "stack" +defaultCompPrograms :: CompPrograms +defaultCompPrograms = CompPrograms "ghc" "ghc-pkg"  data CompileOptions = CompileOptions      { oVerbose       :: Bool @@ -274,12 +282,6 @@ data CompileOptions = CompileOptions  oCabalProgram :: Env => FilePath  oCabalProgram = cabalProgram ?progs -oGhcProgram :: Env => FilePath -oGhcProgram = ghcProgram ?progs - -oGhcPkgProgram :: Env => FilePath -oGhcPkgProgram = ghcPkgProgram ?progs -  defaultCompileOptions :: CompileOptions  defaultCompileOptions =      CompileOptions False Nothing Nothing defaultPrograms | 
