License | Apache-2.0 |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
CabalHelper.Compiletime.Program.CabalInstall
Description
Documentation
newtype CabalInstallVersion Source #
Constructors
CabalInstallVersion | |
Fields |
cabalInstallVersion :: (Verbose, Progs) => IO CabalInstallVersion Source #
installCabalLibV1 :: Env => GhcVersion -> UnpackedCabalVersion -> IO PackageDbDir Source #
installingMessage :: CabalVersion' a -> IO () Source #
callCabalInstall :: Env => PackageDbDir -> CabalSourceDir -> GhcVersion -> UnpackedCabalVersion -> IO () Source #
runSetupHs :: Env => GhcVersion -> FilePath -> FilePath -> UnpackedCabalVersion -> CabalInstallVersion -> IO () Source #
newtype SetupProgram Source #
Constructors
SetupProgram | |
Fields |
compileSetupHs :: Env => GhcVersion -> FilePath -> FilePath -> IO SetupProgram Source #
cabalWithGHCProgOpts :: Progs => [String] Source #
installCabalLibV2 :: Env => GhcVersion -> UnpackedCabalVersion -> PackageEnvFile -> IO () Source #
cabalV2WithGHCProgOpts :: Progs => [String] Source #
data CabalInstallCommand Source #
Constructors
CIConfigure | |
CIBuild |
doCabalInstallCmd :: (QueryEnvI c (Cabal cpt) -> CallProcessWithCwdAndEnv a) -> QueryEnvI c (Cabal cpt) -> Maybe FilePath -> CabalInstallCommand -> [String] -> IO a Source #
readCabalInstallCmd :: QueryEnvI c (Cabal cpt) -> Maybe FilePath -> CabalInstallCommand -> [String] -> IO String Source #
callCabalInstallCmd :: QueryEnvI c (Cabal cpt) -> Maybe FilePath -> CabalInstallCommand -> [String] -> IO () Source #