Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- parsePrintModule :: Config -> Text -> IO (Either [BrittanyError] Text)
- staticDefaultConfig :: Config
- forwardOptionsSyntaxExtsEnabled :: ForwardOptions
- userConfigPath :: IO FilePath
- findLocalConfigPath :: FilePath -> IO (Maybe FilePath)
- readConfigs :: CConfig Option -> [FilePath] -> MaybeT IO Config
- readConfigsWithUserConfig :: CConfig Option -> [FilePath] -> MaybeT IO Config
- type Config = CConfig Identity
- 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)
- data CErrorHandlingConfig f = ErrorHandlingConfig {}
- data CForwardOptions f = ForwardOptions {
- _options_ghc :: f [String]
- data CPreProcessorConfig f = PreProcessorConfig {
- _ppconf_CPPMode :: f (Last CPPMode)
- _ppconf_hackAroundIncludes :: f (Last Bool)
- data BrittanyError
Documentation
parsePrintModule :: Config -> Text -> IO (Either [BrittanyError] Text) Source #
Exposes the transformation in an pseudo-pure fashion. The signature
contains IO
due to the GHC API not exposing a pure parsing function, but
there should be no observable effects.
Note that this function ignores/resets all config values regarding
debugging, i.e. it will never use trace
/write to stderr.
Note that the ghc parsing function used internally currently is wrapped in
mask_
, so cannot be killed easily. If you don't control the input, you
may wish to put some proper upper bound on the input's size as a timeout
won't do.
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)
Config | |
|
Instances
data CDebugConfig f Source #
DebugConfig | |
|
Instances
data CLayoutConfig f Source #
Instances
data CErrorHandlingConfig f Source #
ErrorHandlingConfig | |
|
Instances
data CForwardOptions f Source #
ForwardOptions | |
|
Instances
data CPreProcessorConfig f Source #
PreProcessorConfig | |
|
Instances
data BrittanyError Source #
ErrorInput String | parsing failed |
ErrorUnusedComment String | internal error: some comment went missing |
ErrorMacroConfig String String | in-source config string parsing error; first argument is the parser output and second the corresponding, ill-formed input. |
LayoutWarning String | some warning |
Data ast => ErrorUnknownNode String (GenLocated SrcSpan ast) | internal error: pretty-printing is not implemented for type of node in the syntax-tree |
ErrorOutputCheck | checking the output for syntactic validity failed |