| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Ormolu.Config
Description
Configuration options used by the tool.
Synopsis
- data Config region = Config {
- cfgDynOptions :: ![DynOption]
- cfgFixityOverrides :: !FixityOverrides
- cfgModuleReexports :: !ModuleReexports
- cfgDependencies :: !(Set PackageName)
- 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
- overapproximatedDependencies :: Config region -> Set PackageName
- regionIndicesToDeltas :: Int -> RegionIndices -> RegionDeltas
- newtype DynOption = DynOption {}
- dynOptionToLocatedStr :: DynOption -> Located String
- data PrinterOpts f = PrinterOpts {
- poIndentation :: f Int
- poColumnLimit :: f ColumnLimit
- poFunctionArrows :: f FunctionArrowsStyle
- poCommaStyle :: f CommaStyle
- poImportExportStyle :: f ImportExportStyle
- poIndentWheres :: f Bool
- poRecordBraceSpace :: f Bool
- poNewlinesBetweenDecls :: f Int
- poHaddockStyle :: f HaddockPrintStyle
- poHaddockStyleModule :: f HaddockPrintStyleModule
- poLetStyle :: f LetStyle
- poInStyle :: f InStyle
- poSingleConstraintParens :: f SingleConstraintParens
- poSingleDerivingParens :: f SingleDerivingParens
- poUnicode :: f Unicode
- poRespectful :: f Bool
- type PrinterOptsPartial = PrinterOpts Maybe
- type PrinterOptsTotal = PrinterOpts Identity
- defaultPrinterOpts :: PrinterOpts Identity
- defaultPrinterOptsYaml :: String
- fillMissingPrinterOpts :: forall f. Applicative f => PrinterOpts Maybe -> PrinterOpts f -> PrinterOpts f
- resolvePrinterOpts :: [PrinterOptsPartial] -> PrinterOptsTotal
- data CommaStyle
- data FunctionArrowsStyle
- data HaddockPrintStyle
- data HaddockPrintStyleModule
- data ImportExportStyle
- data LetStyle
- data InStyle
- data Unicode
- data ColumnLimit
- data SingleDerivingParens
- parsePrinterOptsCLI :: Applicative f => (forall a. PrinterOptsFieldType a => String -> String -> String -> f (Maybe a)) -> f (PrinterOpts Maybe)
- parsePrinterOptType :: PrinterOptsFieldType a => String -> Either String a
- data ConfigNotFound = ConfigNotFound {
- searchDirs :: [FilePath]
- findConfigFile :: FilePath -> IO (Either ConfigNotFound FilePath)
- configFileName :: FilePath
- data FourmoluConfig = FourmoluConfig {}
- emptyConfig :: FourmoluConfig
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] # | |
| Show ColorMode Source # | |
| Eq ColorMode Source # | |
data RegionIndices Source #
Region selection as the combination of start and end line numbers.
Constructors
| RegionIndices | |
Fields
| |
Instances
| Show RegionIndices Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> RegionIndices -> ShowS # show :: RegionIndices -> String # showList :: [RegionIndices] -> ShowS # | |
| Eq RegionIndices Source # | |
Defined in Ormolu.Config Methods (==) :: RegionIndices -> RegionIndices -> Bool # (/=) :: RegionIndices -> RegionIndices -> Bool # | |
data RegionDeltas Source #
Region selection as the length of the literal prefix and the literal suffix.
Constructors
| RegionDeltas | |
Fields
| |
Instances
| Show RegionDeltas Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> RegionDeltas -> ShowS # show :: RegionDeltas -> String # showList :: [RegionDeltas] -> ShowS # | |
| Eq RegionDeltas Source # | |
Defined in Ormolu.Config | |
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
| Show SourceType Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> SourceType -> ShowS # show :: SourceType -> String # showList :: [SourceType] -> ShowS # | |
| Eq SourceType Source # | |
Defined in Ormolu.Config | |
defaultConfig :: Config RegionIndices Source #
Default .Config RegionIndices
overapproximatedDependencies :: Config region -> Set PackageName Source #
Return all dependencies of the module. This includes both the declared dependencies of the component we are working with and all potential module re-export targets.
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
| Show DynOption Source # | |
| Eq DynOption Source # | |
| Ord DynOption Source # | |
Fourmolu configuration
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.
fillMissingPrinterOpts :: forall f. Applicative f => PrinterOpts Maybe -> 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.
resolvePrinterOpts :: [PrinterOptsPartial] -> PrinterOptsTotal Source #
Apply the given configuration in order (later options override earlier).
data CommaStyle Source #
Instances
| FromJSON CommaStyle Source # | |
Defined in Ormolu.Config.Gen | |
| Bounded CommaStyle Source # | |
Defined in Ormolu.Config.Gen | |
| Enum CommaStyle Source # | |
Defined in Ormolu.Config.Gen Methods 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.Gen Methods showsPrec :: Int -> CommaStyle -> ShowS # show :: CommaStyle -> String # showList :: [CommaStyle] -> ShowS # | |
| Eq CommaStyle Source # | |
Defined in Ormolu.Config.Gen | |
data FunctionArrowsStyle Source #
Constructors
| TrailingArrows | |
| LeadingArrows | |
| LeadingArgsArrows |
Instances
data HaddockPrintStyle Source #
Constructors
| HaddockSingleLine | |
| HaddockMultiLine | |
| HaddockMultiLineCompact |
Instances
data HaddockPrintStyleModule Source #
Constructors
| PrintStyleInherit | |
| PrintStyleOverride HaddockPrintStyle |
Instances
| FromJSON HaddockPrintStyleModule Source # | |
Defined in Ormolu.Config.Gen Methods parseJSON :: Value -> Parser HaddockPrintStyleModule # parseJSONList :: Value -> Parser [HaddockPrintStyleModule] # | |
| Show HaddockPrintStyleModule Source # | |
Defined in Ormolu.Config.Gen Methods showsPrec :: Int -> HaddockPrintStyleModule -> ShowS # show :: HaddockPrintStyleModule -> String # showList :: [HaddockPrintStyleModule] -> ShowS # | |
| Eq HaddockPrintStyleModule Source # | |
Defined in Ormolu.Config.Gen Methods (==) :: HaddockPrintStyleModule -> HaddockPrintStyleModule -> Bool # (/=) :: HaddockPrintStyleModule -> HaddockPrintStyleModule -> Bool # | |
data ImportExportStyle Source #
Instances
Constructors
| LetAuto | |
| LetInline | |
| LetNewline | |
| LetMixed |
Instances
| FromJSON LetStyle Source # | |
Defined in Ormolu.Config.Gen | |
| Bounded LetStyle Source # | |
| Enum LetStyle Source # | |
Defined in Ormolu.Config.Gen | |
| Show LetStyle Source # | |
| Eq LetStyle Source # | |
Constructors
| InLeftAlign | |
| InRightAlign | |
| InNoSpace |
Instances
| FromJSON InStyle Source # | |
Defined in Ormolu.Config.Gen | |
| Bounded InStyle Source # | |
| Enum InStyle Source # | |
| Show InStyle Source # | |
| Eq InStyle Source # | |
Constructors
| UnicodeDetect | |
| UnicodeAlways | |
| UnicodeNever |
Instances
| FromJSON Unicode Source # | |
Defined in Ormolu.Config.Gen | |
| Bounded Unicode Source # | |
| Enum Unicode Source # | |
| Show Unicode Source # | |
| Eq Unicode Source # | |
data ColumnLimit Source #
Constructors
| NoLimit | |
| ColumnLimit Int |
Instances
| FromJSON ColumnLimit Source # | |
Defined in Ormolu.Config.Gen | |
| Show ColumnLimit Source # | |
Defined in Ormolu.Config.Gen Methods showsPrec :: Int -> ColumnLimit -> ShowS # show :: ColumnLimit -> String # showList :: [ColumnLimit] -> ShowS # | |
| Eq ColumnLimit Source # | |
Defined in Ormolu.Config.Gen | |
data SingleDerivingParens Source #
Constructors
| DerivingAuto | |
| DerivingAlways | |
| DerivingNever |
Instances
parsePrinterOptsCLI :: Applicative f => (forall a. PrinterOptsFieldType a => String -> String -> String -> f (Maybe a)) -> f (PrinterOpts Maybe) Source #
Loading Fourmolu configuration
data ConfigNotFound Source #
Constructors
| ConfigNotFound | |
Fields
| |
Instances
| Show ConfigNotFound Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> ConfigNotFound -> ShowS # show :: ConfigNotFound -> String # showList :: [ConfigNotFound] -> ShowS # | |
findConfigFile :: FilePath -> IO (Either ConfigNotFound FilePath) Source #
Find a fourmolu configuration file.
Looks for a file named fourmolu.yaml, first in the given path and its parents, and then in the XDG config directory.
configFileName :: FilePath Source #
Expected file name for YAML config.
data FourmoluConfig Source #
Constructors
| FourmoluConfig | |
Instances
| FromJSON FourmoluConfig Source # | |
Defined in Ormolu.Config Methods parseJSON :: Value -> Parser FourmoluConfig # parseJSONList :: Value -> Parser [FourmoluConfig] # | |
| Show FourmoluConfig Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> FourmoluConfig -> ShowS # show :: FourmoluConfig -> String # showList :: [FourmoluConfig] -> ShowS # | |
| Eq FourmoluConfig Source # | |
Defined in Ormolu.Config Methods (==) :: FourmoluConfig -> FourmoluConfig -> Bool # (/=) :: FourmoluConfig -> FourmoluConfig -> Bool # | |