Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Configuration options used by the tool.
Synopsis
- data Config region = Config {
- cfgDynOptions :: ![DynOption]
- cfgFixityOverrides :: FixityMap
- cfgDependencies :: !(Set String)
- 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
- regionIndicesToDeltas :: Int -> RegionIndices -> RegionDeltas
- newtype DynOption = DynOption {}
- dynOptionToLocatedStr :: DynOption -> Located String
- data PrinterOpts f = PrinterOpts {
- poIndentation :: f Int
- poFunctionArrows :: f FunctionArrowsStyle
- poCommaStyle :: f CommaStyle
- poImportExportStyle :: f ImportExportStyle
- poIndentWheres :: f Bool
- poRecordBraceSpace :: f Bool
- poNewlinesBetweenDecls :: f Int
- poHaddockStyle :: f HaddockPrintStyle
- poRespectful :: f Bool
- type PrinterOptsPartial = PrinterOpts Maybe
- type PrinterOptsTotal = PrinterOpts Identity
- defaultPrinterOpts :: PrinterOptsTotal
- fillMissingPrinterOpts :: forall f. Applicative f => PrinterOptsPartial -> PrinterOpts f -> PrinterOpts f
- data CommaStyle
- data HaddockPrintStyle
- data ImportExportStyle
- loadConfigFile :: FilePath -> IO ConfigFileLoadResult
- configFileName :: FilePath
- data FourmoluConfig = FourmoluConfig {}
- emptyConfig :: FourmoluConfig
- data ConfigFileLoadResult
- data PrinterOptsFieldMeta a where
- PrinterOptsFieldMeta :: PrinterOptsFieldType a => {..} -> PrinterOptsFieldMeta a
- class PrinterOptsFieldType a where
- printerOptsMeta :: PrinterOpts PrinterOptsFieldMeta
- overFields :: (forall a. f a -> g a) -> PrinterOpts f -> PrinterOpts g
- overFieldsM :: Applicative m => (forall a. f a -> m (g a)) -> PrinterOpts f -> m (PrinterOpts g)
Documentation
Ormolu configuration.
Config | |
|
Instances
Whether to use colors and other features of ANSI terminals.
Instances
Bounded ColorMode Source # | |
Enum ColorMode Source # | |
Defined in Ormolu.Terminal 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] # | |
Show ColorMode Source # | |
Eq ColorMode Source # | |
data RegionIndices Source #
Region selection as the combination of start and end line numbers.
RegionIndices | |
|
Instances
Show RegionIndices Source # | |
Defined in Ormolu.Config showsPrec :: Int -> RegionIndices -> ShowS # show :: RegionIndices -> String # showList :: [RegionIndices] -> ShowS # | |
Eq RegionIndices Source # | |
Defined in Ormolu.Config (==) :: RegionIndices -> RegionIndices -> Bool # (/=) :: RegionIndices -> RegionIndices -> Bool # |
data RegionDeltas Source #
Region selection as the length of the literal prefix and the literal suffix.
RegionDeltas | |
|
Instances
Show RegionDeltas Source # | |
Defined in Ormolu.Config showsPrec :: Int -> RegionDeltas -> ShowS # show :: RegionDeltas -> String # showList :: [RegionDeltas] -> ShowS # | |
Eq RegionDeltas Source # | |
Defined in Ormolu.Config (==) :: RegionDeltas -> RegionDeltas -> Bool # (/=) :: RegionDeltas -> RegionDeltas -> Bool # |
data SourceType Source #
Type of sources that can be formatted by Ormolu.
ModuleSource | Consider the input as a regular Haskell module |
SignatureSource | Consider the input as a Backpack module signature |
Instances
Show SourceType Source # | |
Defined in Ormolu.Config showsPrec :: Int -> SourceType -> ShowS # show :: SourceType -> String # showList :: [SourceType] -> ShowS # | |
Eq SourceType Source # | |
Defined in Ormolu.Config (==) :: SourceType -> SourceType -> Bool # (/=) :: SourceType -> SourceType -> Bool # |
defaultConfig :: Config RegionIndices Source #
Default
.Config
RegionIndices
regionIndicesToDeltas Source #
:: Int | Total number of lines in the input |
-> RegionIndices | Region indices |
-> RegionDeltas | Region deltas |
Convert RegionIndices
into RegionDeltas
.
A wrapper for dynamic options.
Fourmolu configuration
data PrinterOpts f Source #
Options controlling formatting output.
PrinterOpts | |
|
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.
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
Bounded CommaStyle Source # | |
Defined in Ormolu.Config.Types minBound :: CommaStyle # maxBound :: CommaStyle # | |
Enum CommaStyle Source # | |
Defined in Ormolu.Config.Types succ :: CommaStyle -> CommaStyle # pred :: CommaStyle -> CommaStyle # toEnum :: Int -> CommaStyle # fromEnum :: CommaStyle -> Int # enumFrom :: CommaStyle -> [CommaStyle] # enumFromThen :: CommaStyle -> CommaStyle -> [CommaStyle] # enumFromTo :: CommaStyle -> CommaStyle -> [CommaStyle] # enumFromThenTo :: CommaStyle -> CommaStyle -> CommaStyle -> [CommaStyle] # | |
Show CommaStyle Source # | |
Defined in Ormolu.Config.Types showsPrec :: Int -> CommaStyle -> ShowS # show :: CommaStyle -> String # showList :: [CommaStyle] -> ShowS # | |
PrinterOptsFieldType CommaStyle Source # | |
Defined in Ormolu.Config | |
Eq CommaStyle Source # | |
Defined in Ormolu.Config.Types (==) :: CommaStyle -> CommaStyle -> Bool # (/=) :: CommaStyle -> CommaStyle -> Bool # |
data HaddockPrintStyle Source #
Instances
data ImportExportStyle Source #
Instances
Loading Fourmolu configuration
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 FourmoluConfig Source #
Instances
FromJSON FourmoluConfig Source # | |
Defined in Ormolu.Config parseJSON :: Value -> Parser FourmoluConfig # parseJSONList :: Value -> Parser [FourmoluConfig] # | |
Show FourmoluConfig Source # | |
Defined in Ormolu.Config showsPrec :: Int -> FourmoluConfig -> ShowS # show :: FourmoluConfig -> String # showList :: [FourmoluConfig] -> ShowS # | |
Eq FourmoluConfig Source # | |
Defined in Ormolu.Config (==) :: FourmoluConfig -> FourmoluConfig -> Bool # (/=) :: FourmoluConfig -> FourmoluConfig -> Bool # |
data ConfigFileLoadResult Source #
The result of calling loadConfigFile
.
ConfigLoaded FilePath FourmoluConfig | |
ConfigParseError FilePath ParseException | |
ConfigNotFound [FilePath] |
Instances
Show ConfigFileLoadResult Source # | |
Defined in Ormolu.Config showsPrec :: Int -> ConfigFileLoadResult -> ShowS # show :: ConfigFileLoadResult -> String # showList :: [ConfigFileLoadResult] -> ShowS # |
Utilities
data PrinterOptsFieldMeta a where Source #
Source of truth for how PrinterOpts is parsed from configuration sources.
PrinterOptsFieldMeta | |
|
class PrinterOptsFieldType a where Source #
Nothing
Instances
overFields :: (forall a. f a -> g a) -> PrinterOpts f -> PrinterOpts g Source #
overFieldsM :: Applicative m => (forall a. f a -> m (g a)) -> PrinterOpts f -> m (PrinterOpts g) Source #