fourmolu-0.3.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.

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.

ormoluFile cfg path =
  liftIO (readFile path) >>= ormolu cfg path

ormoluStdin Source #

Arguments

:: MonadIO m 
=> Config RegionIndices

Ormolu configuration

-> m Text

Resulting rendition

Read input from stdin and format it.

ormoluStdin cfg =
  liftIO (hGetContents stdin) >>= ormolu cfg "<stdin>"

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 #

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

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

Methods

parseJSON :: Value -> Parser PrinterOptsPartial

parseJSONList :: Value -> Parser [PrinterOptsPartial]

Generic (PrinterOpts f) Source # 
Instance details

Defined in Ormolu.Config

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

type Rep (PrinterOpts f) = D1 ('MetaData "PrinterOpts" "Ormolu.Config" "fourmolu-0.3.0.0-inplace" '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 "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 FilePath [SrcSpan]

Original and resulting ASTs differ

OrmoluNonIdempotentOutput RealSrcLoc Text Text

Formatted source code is not idempotent

OrmoluUnrecognizedOpts (NonEmpty String)

Some GHC options were not recognized

withPrettyOrmoluExceptions Source #

Arguments

:: IO a

Action that may throw the exception

-> IO a 

Inside this wrapper OrmoluException will be caught and displayed nicely using displayException.