| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
BuildEnv.Config
Description
Configuration options for build-env
Synopsis
- data BuildStrategy
- = Execute RunStrategy
 - | Script { 
- scriptPath :: !(SymbolicPath CWD File)
 - useVariables :: !Bool
 
 
 - data RunStrategy
 - data AsyncSem
 - semDescription :: AsyncSem -> Text
 - type Args = [String]
 - data UnitArgs = UnitArgs {
- configureArgs :: !Args
 - mbHaddockArgs :: !(Maybe Args)
 - registerArgs :: !Args
 
 - data Compiler = Compiler {
- ghcPath :: !(AbsolutePath File)
 - ghcPkgPath :: !(AbsolutePath File)
 
 - data Cabal = Cabal {
- cabalPath :: !(AbsolutePath File)
 - globalCabalArgs :: !Args
 
 - newtype IndexState = IndexState Text
 - data Paths use = Paths {
- fetchDir :: !(SymbolicPath Project (Dir Fetch))
 - buildPaths :: BuildPaths use
 
 - data family BuildPaths use
 - data PathUsability
 - canonicalizePaths :: Compiler -> BuildStrategy -> SymbolicPath CWD (Dir Project) -> Paths Raw -> IO (Paths ForPrep, Paths ForBuild)
 - data TempDirPermanence
 - newtype Verbosity where
 - quietMsg :: Verbosity -> Text -> IO ()
 - normalMsg :: Verbosity -> Text -> IO ()
 - verboseMsg :: Verbosity -> Text -> IO ()
 - debugMsg :: Verbosity -> Text -> IO ()
 - ghcVerbosity :: Verbosity -> String
 - ghcPkgVerbosity :: Verbosity -> String
 - cabalVerbosity :: Verbosity -> String
 - setupVerbosity :: Verbosity -> String
 - data Counter = Counter {
- counterRef :: !(IORef Word)
 - counterMax :: !Word
 
 - data Style
 - hostStyle :: Style
 - pATHSeparator :: Style -> String
 
Build strategy
data BuildStrategy Source #
Build strategy for buildPlan.
Constructors
| Execute RunStrategy | Execute the build plan in-place.  | 
| Script | Output a build script that can be run later.  | 
Fields 
  | |
Instances
| Show BuildStrategy Source # | |
Defined in BuildEnv.Config Methods showsPrec :: Int -> BuildStrategy -> ShowS # show :: BuildStrategy -> String # showList :: [BuildStrategy] -> ShowS #  | |
data RunStrategy Source #
How to execute a build plan.
Constructors
| TopoSort | Topologically sort the cabal build plan, and build the packages in sequence.  | 
| Async | Asynchronously build all the packages, with each package waiting on its dependencies.  | 
Fields 
  | |
Instances
| Show RunStrategy Source # | |
Defined in BuildEnv.Config Methods showsPrec :: Int -> RunStrategy -> ShowS # show :: RunStrategy -> String # showList :: [RunStrategy] -> ShowS #  | |
What kind of semaphore to use in buildPlan?
semDescription :: AsyncSem -> Text Source #
A description of the kind of semaphore we are using to control concurrency.
Passing arguments
Arguments specific to a unit.
Constructors
| UnitArgs | |
Fields 
  | |
ghc and cabal-install executables
Paths to the ghc and ghc-pkg executables.
Constructors
| Compiler | |
Fields 
  | |
Path to the cabal-install executable.
Constructors
| Cabal | |
Fields 
  | |
Hackage index state
newtype IndexState Source #
Hackage index-state specification, e.g. 2022-12-25T00:00:00Z.
Constructors
| IndexState Text | 
Instances
| Show IndexState Source # | |
Defined in BuildEnv.Config Methods showsPrec :: Int -> IndexState -> ShowS # show :: IndexState -> String # showList :: [IndexState] -> ShowS #  | |
| Eq IndexState Source # | |
Defined in BuildEnv.Config  | |
Directory structure
The directory structure relevant to preparing and carrying out a build plan.
Constructors
| Paths | |
Fields 
  | |
data family BuildPaths use Source #
The directory structure relevant to executing a build plan.
Instances
| Show (BuildPaths 'ForBuild) Source # | |
Defined in BuildEnv.Config  | |
| Show (BuildPaths 'ForPrep) Source # | |
Defined in BuildEnv.Config  | |
| Show (BuildPaths 'Raw) Source # | |
Defined in BuildEnv.Config  | |
| data BuildPaths 'ForBuild Source # | |
Defined in BuildEnv.Config data BuildPaths 'ForBuild = BuildPaths { 
  | |
| data BuildPaths 'ForPrep Source # | |
Defined in BuildEnv.Config data BuildPaths 'ForPrep = BuildPathsForPrep { 
  | |
| data BuildPaths 'Raw Source # | |
Defined in BuildEnv.Config data BuildPaths 'Raw = RawBuildPaths { 
  | |
data PathUsability Source #
The appropriate stage at which to use a filepath.
canonicalizePaths :: Compiler -> BuildStrategy -> SymbolicPath CWD (Dir Project) -> Paths Raw -> IO (Paths ForPrep, Paths ForBuild) Source #
Canonicalise raw Paths, computing the appropriate directory structure
 for preparing and executing a build, respectively.
Handling of temporary directories
data TempDirPermanence Source #
How to handle deletion of temporary directories.
Constructors
| DeleteTempDirs | |
| Don'tDeleteTempDirs | 
Instances
| Show TempDirPermanence Source # | |
Defined in BuildEnv.Config Methods showsPrec :: Int -> TempDirPermanence -> ShowS # show :: TempDirPermanence -> String # showList :: [TempDirPermanence] -> ShowS #  | |
Logging verbosity
Verbosity level for the build-env package.
The default verbosity level is Normal (1).
Bundled Patterns
| pattern Quiet :: Verbosity | |
| pattern Normal :: Verbosity | |
| pattern Verbose :: Verbosity | |
| pattern Debug :: Verbosity | 
Instances
| Num Verbosity Source # | |
Defined in BuildEnv.Config  | |
| Show Verbosity Source # | |
| Eq Verbosity Source # | |
| Ord Verbosity Source # | |
ghcVerbosity :: Verbosity -> String Source #
ghcPkgVerbosity :: Verbosity -> String Source #
cabalVerbosity :: Verbosity -> String Source #
setupVerbosity :: Verbosity -> String Source #
Reporting progress
A counter to measure progress, as units are compiled.
Constructors
| Counter | |
Fields 
  | |
OS specifics
Whether to use Posix or Windows style:
- for executables, 
./progvsprog.exe, - for the path separator, 
:vs;. 
Constructors
| PosixStyle | |
| WinStyle | 
pATHSeparator :: Style -> String Source #
OS-dependent separator for the PATH environment variable.