Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CommandLineOptions = CommandLineOptions {}
- data BehaviorAdjustment
- data Flags = Flags {
- _verbosity :: Int
- _dryRun :: Bool
- _upgrade :: Bool
- _roundtrip :: Bool
- _validate :: Bool
- _compilerFlavor :: CompilerFlavor
- _cabalFlagAssignments :: Set (FlagName, Bool)
- _buildEnv :: EnvSet
- parseProgramArguments :: IO CommandLineOptions
- parseProgramArguments' :: [String] -> IO CommandLineOptions
- handleBehaviorAdjustment :: (MonadIO m, Functor m) => BehaviorAdjustment -> CabalT m ()
Documentation
data CommandLineOptions Source #
This data type is an abomination. It represent information,
provided on command line. Part of such information provides
means to create initial CabalT
state and is stored in
_flags
field. See newCabalInfo
.
Other, much greater part represent changes to already created
state. They are stored in _adjustment
field.
All this can be understood from (simplified) types:
type CabalT m a = StateT CabalInfo m a newCabalInfo :: Flags -> IO CabalInfo handleBehaviorAdjustment :: BehaviorAdjustment -> CabalT IO ()
data BehaviorAdjustment Source #
This data type represents changes to CabalT
state,
requested at command line.
This record supplies enough information to locate and load a debianization or a cabal file from the IO monad.
Flags | |
|
handleBehaviorAdjustment :: (MonadIO m, Functor m) => BehaviorAdjustment -> CabalT m () Source #