fourmolu-0.7.0.0: A formatter for Haskell source code
Safe HaskellNone
LanguageHaskell2010

Ormolu

Description

A formatter for Haskell source code.

Synopsis

Documentation

ormolu Source #

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 String because that's what GHC parser accepts.
  • Needs IO because some functions from GHC that are necessary to setup parsing context require IO. 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.

ormoluFile Source #

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.

ormoluStdin Source #

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.

data Config region Source #

Ormolu configuration.

Constructors

Config 

Fields

Instances

Instances details
Functor Config Source # 
Instance details

Defined in Ormolu.Config

Methods

fmap :: (a -> b) -> Config a -> Config b #

(<$) :: a -> Config b -> Config a #

Eq region => Eq (Config region) Source # 
Instance details

Defined in Ormolu.Config

Methods

(==) :: Config region -> Config region -> Bool #

(/=) :: Config region -> Config region -> Bool #

Show region => Show (Config region) Source # 
Instance details

Defined in Ormolu.Config

Methods

showsPrec :: Int -> Config region -> ShowS #

show :: Config region -> String #

showList :: [Config region] -> ShowS #

Generic (Config region) Source # 
Instance details

Defined in Ormolu.Config

Associated Types

type Rep (Config region) :: Type -> Type #

Methods

from :: Config region -> Rep (Config region) x #

to :: Rep (Config region) x -> Config region #

type Rep (Config region) Source # 
Instance details

Defined in Ormolu.Config

data ColorMode Source #

Whether to use colors and other features of ANSI terminals.

Constructors

Never 
Always 
Auto 

data RegionIndices Source #

Region selection as the combination of start and end line numbers.

Constructors

RegionIndices 

Fields

Instances

Instances details
Eq RegionIndices Source # 
Instance details

Defined in Ormolu.Config

Show RegionIndices Source # 
Instance details

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

Instances details
Eq SourceType Source # 
Instance details

Defined in Ormolu.Config

Show SourceType Source # 
Instance details

Defined in Ormolu.Config

detectSourceType :: FilePath -> SourceType Source #

Detect SourceType based on the file extension.

newtype DynOption Source #

A wrapper for dynamic options.

Constructors

DynOption 

Fields

Instances

Instances details
Eq DynOption Source # 
Instance details

Defined in Ormolu.Config

Ord DynOption Source # 
Instance details

Defined in Ormolu.Config

Show DynOption Source # 
Instance details

Defined in Ormolu.Config

data PrinterOpts f Source #

Options controlling formatting output.

Constructors

PrinterOpts 

Fields

Instances

Instances details
Eq PrinterOptsTotal Source # 
Instance details

Defined in Ormolu.Config

Eq PrinterOptsPartial Source # 
Instance details

Defined in Ormolu.Config

Show PrinterOptsTotal Source # 
Instance details

Defined in Ormolu.Config

Show PrinterOptsPartial Source # 
Instance details

Defined in Ormolu.Config

Semigroup PrinterOptsPartial Source # 
Instance details

Defined in Ormolu.Config

Monoid PrinterOptsPartial Source # 
Instance details

Defined in Ormolu.Config

FromJSON PrinterOptsPartial Source # 
Instance details

Defined in Ormolu.Config

Generic (PrinterOpts f) Source # 
Instance details

Defined in Ormolu.Config.Types

Associated Types

type Rep (PrinterOpts f) :: Type -> Type #

Methods

from :: PrinterOpts f -> Rep (PrinterOpts f) x #

to :: Rep (PrinterOpts f) x -> PrinterOpts f #

type Rep (PrinterOpts f) Source # 
Instance details

Defined in Ormolu.Config.Types

type Rep (PrinterOpts f) = D1 ('MetaData "PrinterOpts" "Ormolu.Config.Types" "fourmolu-0.7.0.0-5XfjyxWOfXPGxk6UjLW41x" 'False) (C1 ('MetaCons "PrinterOpts" 'PrefixI 'True) (((S1 ('MetaSel ('Just "poIndentation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Int)) :*: S1 ('MetaSel ('Just "poCommaStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f CommaStyle))) :*: (S1 ('MetaSel ('Just "poImportExportCommaStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f CommaStyle)) :*: S1 ('MetaSel ('Just "poIndentWheres") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Bool)))) :*: ((S1 ('MetaSel ('Just "poRecordBraceSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Bool)) :*: S1 ('MetaSel ('Just "poDiffFriendlyImportExport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Bool))) :*: (S1 ('MetaSel ('Just "poRespectful") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Bool)) :*: (S1 ('MetaSel ('Just "poHaddockStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f HaddockPrintStyle)) :*: S1 ('MetaSel ('Just "poNewlinesBetweenDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f Int)))))))

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.

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

withPrettyOrmoluExceptions Source #

Arguments

:: ColorMode

Color mode

-> IO ExitCode

Action that may throw an exception

-> IO ExitCode 

Inside this wrapper OrmoluException will be caught and displayed nicely.