| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ormolu.Config
Description
Configuration options used by the tool.
Synopsis
- data Config region = Config {
- cfgDynOptions :: ![DynOption]
- cfgUnsafe :: !Bool
- cfgDebug :: !Bool
- cfgCheckIdempotence :: !Bool
- cfgSourceType :: !SourceType
- cfgColorMode :: !ColorMode
- cfgRegion :: !region
- cfgPrinterOpts :: !PrinterOptsTotal
- data ColorMode
- data RegionIndices = RegionIndices {
- regionStartLine :: !(Maybe Int)
- regionEndLine :: !(Maybe Int)
- data RegionDeltas = RegionDeltas {}
- data SourceType
- defaultConfig :: Config RegionIndices
- data PrinterOpts f = PrinterOpts {
- poIndentation :: f Int
- poCommaStyle :: f CommaStyle
- poImportExportCommaStyle :: f CommaStyle
- poIndentWheres :: f Bool
- poRecordBraceSpace :: f Bool
- poDiffFriendlyImportExport :: f Bool
- poRespectful :: f Bool
- poHaddockStyle :: f HaddockPrintStyle
- poNewlinesBetweenDecls :: f Int
- type PrinterOptsPartial = PrinterOpts Maybe
- type PrinterOptsTotal = PrinterOpts Identity
- defaultPrinterOpts :: PrinterOptsTotal
- loadConfigFile :: FilePath -> IO ConfigFileLoadResult
- configFileName :: FilePath
- data ConfigFileLoadResult
- fillMissingPrinterOpts :: forall f. Applicative f => PrinterOptsPartial -> PrinterOpts f -> PrinterOpts f
- data CommaStyle
- data HaddockPrintStyle
- regionIndicesToDeltas :: Int -> RegionIndices -> RegionDeltas
- newtype DynOption = DynOption {}
- dynOptionToLocatedStr :: DynOption -> Located String
Documentation
Ormolu configuration.
Constructors
| Config | |
Fields
| |
Instances
Whether to use colors and other features of ANSI terminals.
Instances
| Bounded ColorMode Source # | |
| Enum ColorMode Source # | |
Defined in Ormolu.Terminal Methods succ :: ColorMode -> ColorMode # pred :: ColorMode -> ColorMode # fromEnum :: ColorMode -> Int # enumFrom :: ColorMode -> [ColorMode] # enumFromThen :: ColorMode -> ColorMode -> [ColorMode] # enumFromTo :: ColorMode -> ColorMode -> [ColorMode] # enumFromThenTo :: ColorMode -> ColorMode -> ColorMode -> [ColorMode] # | |
| Eq ColorMode Source # | |
| Show ColorMode Source # | |
data RegionIndices Source #
Region selection as the combination of start and end line numbers.
Constructors
| RegionIndices | |
Fields
| |
Instances
| Eq RegionIndices Source # | |
Defined in Ormolu.Config Methods (==) :: RegionIndices -> RegionIndices -> Bool # (/=) :: RegionIndices -> RegionIndices -> Bool # | |
| Show RegionIndices Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> RegionIndices -> ShowS # show :: RegionIndices -> String # showList :: [RegionIndices] -> ShowS # | |
data RegionDeltas Source #
Region selection as the length of the literal prefix and the literal suffix.
Constructors
| RegionDeltas | |
Fields
| |
Instances
| Eq RegionDeltas Source # | |
Defined in Ormolu.Config | |
| Show RegionDeltas Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> RegionDeltas -> ShowS # show :: RegionDeltas -> String # showList :: [RegionDeltas] -> ShowS # | |
data SourceType Source #
Type of sources that can be formatted by Ormolu.
Constructors
| ModuleSource | Consider the input as a regular Haskell module |
| SignatureSource | Consider the input as a Backpack module signature |
Instances
| Eq SourceType Source # | |
Defined in Ormolu.Config | |
| Show SourceType Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> SourceType -> ShowS # show :: SourceType -> String # showList :: [SourceType] -> ShowS # | |
defaultConfig :: Config RegionIndices Source #
Default .Config RegionIndices
data PrinterOpts f Source #
Options controlling formatting output.
Constructors
| PrinterOpts | |
Fields
| |
Instances
type PrinterOptsPartial = PrinterOpts Maybe Source #
A version of PrinterOpts where any field can be empty.
This corresponds to the information in a config file or in CLI options.
type PrinterOptsTotal = PrinterOpts Identity Source #
A version of PrinterOpts without empty fields.
loadConfigFile :: FilePath -> IO ConfigFileLoadResult Source #
Read options from a config file, if found.
Looks recursively in parent folders, then in XdgConfig,
for a file named fourmolu.yaml.
configFileName :: FilePath Source #
Expected file name for YAML config.
data ConfigFileLoadResult Source #
The result of calling loadConfigFile.
Constructors
| ConfigLoaded FilePath PrinterOptsPartial | |
| ConfigParseError FilePath (Pos, String) | |
| ConfigNotFound [FilePath] |
Instances
| Eq ConfigFileLoadResult Source # | |
Defined in Ormolu.Config Methods (==) :: ConfigFileLoadResult -> ConfigFileLoadResult -> Bool # (/=) :: ConfigFileLoadResult -> ConfigFileLoadResult -> Bool # | |
| Show ConfigFileLoadResult Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> ConfigFileLoadResult -> ShowS # show :: ConfigFileLoadResult -> String # showList :: [ConfigFileLoadResult] -> ShowS # | |
fillMissingPrinterOpts :: forall f. Applicative f => PrinterOptsPartial -> PrinterOpts f -> PrinterOpts f Source #
Fill the field values that are Nothing in the first argument
with the values of the corresponding fields of the second argument.
data CommaStyle Source #
Instances
data HaddockPrintStyle Source #
Constructors
| HaddockSingleLine | |
| HaddockMultiLine |
Instances
regionIndicesToDeltas Source #
Arguments
| :: Int | Total number of lines in the input |
| -> RegionIndices | Region indices |
| -> RegionDeltas | Region deltas |
Convert RegionIndices into RegionDeltas.
A wrapper for dynamic options.
Constructors
| DynOption | |
Fields | |
Instances
| Eq DynOption Source # | |
| Ord DynOption Source # | |
| Show DynOption Source # | |