Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data CConfig f = Config {}
- data CDebugConfig f = DebugConfig {
- _dconf_dump_config :: f (Last Bool)
- _dconf_dump_annotations :: f (Last Bool)
- _dconf_dump_ast_unknown :: f (Last Bool)
- _dconf_dump_ast_full :: f (Last Bool)
- _dconf_dump_bridoc_raw :: f (Last Bool)
- _dconf_dump_bridoc_simpl_alt :: f (Last Bool)
- _dconf_dump_bridoc_simpl_floating :: f (Last Bool)
- _dconf_dump_bridoc_simpl_par :: f (Last Bool)
- _dconf_dump_bridoc_simpl_columns :: f (Last Bool)
- _dconf_dump_bridoc_simpl_indent :: f (Last Bool)
- _dconf_dump_bridoc_final :: f (Last Bool)
- _dconf_roundtrip_exactprint_only :: f (Last Bool)
- data CLayoutConfig f = LayoutConfig {
- _lconfig_cols :: f (Last Int)
- _lconfig_indentPolicy :: f (Last IndentPolicy)
- _lconfig_indentAmount :: f (Last Int)
- _lconfig_indentWhereSpecial :: f (Last Bool)
- _lconfig_indentListSpecial :: f (Last Bool)
- _lconfig_importColumn :: f (Last Int)
- _lconfig_importAsColumn :: f (Last Int)
- _lconfig_altChooser :: f (Last AltChooser)
- _lconfig_columnAlignMode :: f (Last ColumnAlignMode)
- _lconfig_alignmentLimit :: f (Last Int)
- _lconfig_alignmentBreakOnMultiline :: f (Last Bool)
- _lconfig_hangingTypeSignature :: f (Last Bool)
- _lconfig_reformatModulePreamble :: f (Last Bool)
- _lconfig_allowSingleLineExportList :: f (Last Bool)
- _lconfig_allowHangingQuasiQuotes :: f (Last Bool)
- type DebugConfig = CDebugConfig Identity
- type LayoutConfig = CLayoutConfig Identity
- type Config = CConfig Identity
- cmdlineConfigParser :: CmdParser Identity out (CConfig Option)
- staticDefaultConfig :: Config
- forwardOptionsSyntaxExtsEnabled :: ForwardOptions
- readConfig :: MonadIO m => FilePath -> MaybeT m (Maybe (CConfig Option))
- userConfigPath :: IO FilePath
- findLocalConfigPath :: FilePath -> IO (Maybe FilePath)
- readConfigs :: CConfig Option -> [FilePath] -> MaybeT IO Config
- readConfigsWithUserConfig :: CConfig Option -> [FilePath] -> MaybeT IO Config
- writeDefaultConfig :: MonadIO m => FilePath -> m ()
- showConfigYaml :: Config -> String
Documentation
Config | |
|
Instances
data CDebugConfig f Source #
DebugConfig | |
|
Instances
data CLayoutConfig f Source #
Instances
type DebugConfig = CDebugConfig Identity Source #
type LayoutConfig = CLayoutConfig Identity Source #
readConfig :: MonadIO m => FilePath -> MaybeT m (Maybe (CConfig Option)) Source #
Reads a config from a file. If the file does not exist, returns Nothing. If the file exists and parsing fails, prints to stderr and aborts the MaybeT. Otherwise succeed via Just. If the second parameter is True and the file does not exist, writes the staticDefaultConfig to the file.
userConfigPath :: IO FilePath Source #
Looks for a user-global config file and return its path. If there is no global config in a system, one will be created.
findLocalConfigPath :: FilePath -> IO (Maybe FilePath) Source #
Searches for a local (per-project) brittany config starting from a given directory
:: CConfig Option | Explicit options, take highest priority |
-> [FilePath] | List of config files to load and merge, highest priority first |
-> MaybeT IO Config |
Reads specified configs.
readConfigsWithUserConfig Source #
:: CConfig Option | Explicit options, take highest priority |
-> [FilePath] | List of config files to load and merge, highest priority first |
-> MaybeT IO Config |
Reads provided configs but also applies the user default configuration (with lowest priority)
writeDefaultConfig :: MonadIO m => FilePath -> m () Source #
showConfigYaml :: Config -> String Source #