| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Ormolu
Description
A formatter for Haskell source code.
Synopsis
- ormolu :: MonadIO m => Config RegionIndices -> FilePath -> String -> m Text
- ormoluFile :: MonadIO m => Config RegionIndices -> FilePath -> m Text
- ormoluStdin :: MonadIO m => Config RegionIndices -> m Text
- 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 SourceType
- defaultConfig :: Config RegionIndices
- detectSourceType :: FilePath -> SourceType
- newtype DynOption = DynOption {}
- 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
- loadConfigFile :: FilePath -> IO ConfigFileLoadResult
- data ConfigFileLoadResult
- configFileName :: FilePath
- fillMissingPrinterOpts :: forall f. Applicative f => PrinterOptsPartial -> PrinterOpts f -> PrinterOpts f
- data OrmoluException- = OrmoluParsingFailed SrcSpan String
- | OrmoluOutputParsingFailed SrcSpan String
- | OrmoluASTDiffers TextDiff [RealSrcSpan]
- | OrmoluNonIdempotentOutput TextDiff
- | OrmoluUnrecognizedOpts (NonEmpty String)
- | OrmoluCabalFileParsingFailed FilePath
- | OrmoluMissingStdinInputFile
- | OrmoluFixityOverridesParseError (ParseErrorBundle Text Void)
 
- withPrettyOrmoluExceptions :: ColorMode -> IO ExitCode -> IO ExitCode
Documentation
Arguments
| :: MonadIO m | |
| => Config RegionIndices | Ormolu configuration | 
| -> FilePath | Location of source file | 
| -> String | Input to format | 
| -> m Text | 
Format a String, return formatted version as Text.
The function
- Takes Stringbecause that's what GHC parser accepts.
- Needs IObecause some functions from GHC that are necessary to setup parsing context requireIO. There should be no visible side-effects though.
- Takes file name just to use it in parse error messages.
- Throws OrmoluException.
NOTE: The caller is responsible for setting the appropriate value in
 the cfgSourceType field. Autodetection of source type won't happen
 here, see detectSourceType.
Arguments
| :: MonadIO m | |
| => Config RegionIndices | Ormolu configuration | 
| -> FilePath | Location of source file | 
| -> m Text | Resulting rendition | 
Load a file and format it. The file stays intact and the rendered
 version is returned as Text.
NOTE: The caller is responsible for setting the appropriate value in
 the cfgSourceType field. Autodetection of source type won't happen
 here, see detectSourceType.
Arguments
| :: MonadIO m | |
| => Config RegionIndices | Ormolu configuration | 
| -> m Text | Resulting rendition | 
Read input from stdin and format it.
NOTE: The caller is responsible for setting the appropriate value in
 the cfgSourceType field. Autodetection of source type won't happen
 here, see detectSourceType.
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 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
detectSourceType :: FilePath -> SourceType Source #
Detect SourceType based on the file extension.
A wrapper for dynamic options.
Constructors
| DynOption | |
| Fields | |
Instances
| Show DynOption Source # | |
| Eq DynOption Source # | |
| Ord DynOption Source # | |
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.
data ConfigFileLoadResult Source #
The result of calling loadConfigFile.
Constructors
| ConfigLoaded FilePath FourmoluConfig | |
| ConfigParseError FilePath ParseException | |
| ConfigNotFound [FilePath] | 
Instances
| Show ConfigFileLoadResult Source # | |
| Defined in Ormolu.Config Methods showsPrec :: Int -> ConfigFileLoadResult -> ShowS # show :: ConfigFileLoadResult -> String # showList :: [ConfigFileLoadResult] -> ShowS # | |
configFileName :: FilePath Source #
Expected file name for YAML config.
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 OrmoluException Source #
Ormolu exception representing all cases when Ormolu can fail.
Constructors
| OrmoluParsingFailed SrcSpan String | Parsing of original source code failed | 
| OrmoluOutputParsingFailed SrcSpan String | Parsing of formatted source code failed | 
| OrmoluASTDiffers TextDiff [RealSrcSpan] | Original and resulting ASTs differ | 
| OrmoluNonIdempotentOutput TextDiff | Formatted source code is not idempotent | 
| OrmoluUnrecognizedOpts (NonEmpty String) | Some GHC options were not recognized | 
| OrmoluCabalFileParsingFailed FilePath | Cabal file parsing failed | 
| OrmoluMissingStdinInputFile | Missing input file path when using stdin input and accounting for .cabal files | 
| OrmoluFixityOverridesParseError (ParseErrorBundle Text Void) | A parse error in a fixity overrides file | 
Instances
| Exception OrmoluException Source # | |
| Defined in Ormolu.Exception Methods toException :: OrmoluException -> SomeException # | |
| Show OrmoluException Source # | |
| Defined in Ormolu.Exception Methods showsPrec :: Int -> OrmoluException -> ShowS # show :: OrmoluException -> String # showList :: [OrmoluException] -> ShowS # | |
| Eq OrmoluException Source # | |
| Defined in Ormolu.Exception Methods (==) :: OrmoluException -> OrmoluException -> Bool # (/=) :: OrmoluException -> OrmoluException -> Bool # | |
withPrettyOrmoluExceptions Source #
Inside this wrapper OrmoluException will be caught and displayed
 nicely.