Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
A formatter for Haskell source code. This module exposes the official stable API, other modules may be not as reliable.
Synopsis
- ormolu :: MonadIO m => Config RegionIndices -> FilePath -> Text -> m Text
- ormoluFile :: MonadIO m => Config RegionIndices -> FilePath -> m Text
- ormoluStdin :: MonadIO m => Config RegionIndices -> m Text
- 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
- data ColorMode
- data RegionIndices = RegionIndices {
- regionStartLine :: !(Maybe Int)
- regionEndLine :: !(Maybe Int)
- data SourceType
- defaultConfig :: Config RegionIndices
- detectSourceType :: FilePath -> SourceType
- refineConfig :: SourceType -> Maybe CabalInfo -> Maybe FixityOverrides -> Maybe ModuleReexports -> Config region -> Config region
- newtype DynOption = DynOption {}
- data CabalSearchResult
- data CabalInfo = CabalInfo {
- ciPackageName :: !PackageName
- ciDynOpts :: ![DynOption]
- ciDependencies :: !(Set PackageName)
- ciCabalFilePath :: !FilePath
- getCabalInfoForSourceFile :: MonadIO m => FilePath -> m CabalSearchResult
- data FixityOverrides
- defaultFixityOverrides :: FixityOverrides
- data ModuleReexports
- defaultModuleReexports :: ModuleReexports
- getDotOrmoluForSourceFile :: MonadIO m => FilePath -> m (FixityOverrides, ModuleReexports)
- data OrmoluException
- = OrmoluParsingFailed SrcSpan String
- | OrmoluOutputParsingFailed SrcSpan String
- | OrmoluASTDiffers TextDiff [RealSrcSpan]
- | OrmoluNonIdempotentOutput TextDiff
- | OrmoluUnrecognizedOpts (NonEmpty String)
- | OrmoluCabalFileParsingFailed FilePath (NonEmpty PError)
- | OrmoluMissingStdinInputFile
- | OrmoluFixityOverridesParseError (ParseErrorBundle Text Void)
- withPrettyOrmoluExceptions :: ColorMode -> IO ExitCode -> IO ExitCode
Top-level formatting functions
:: MonadIO m | |
=> Config RegionIndices | Ormolu configuration |
-> FilePath | Location of source file |
-> Text | Input to format |
-> m Text |
Format a Text
.
The function
- Needs
IO
because 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
.
:: 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
.
:: 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
.
Configuration
Ormolu configuration.
Config | |
|
Instances
Whether to use colors and other features of ANSI terminals.
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 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
detectSourceType :: FilePath -> SourceType Source #
Detect SourceType
based on the file extension.
:: SourceType | Source type to use |
-> Maybe CabalInfo | Cabal info for the file, if available |
-> Maybe FixityOverrides | Fixity overrides, if available |
-> Maybe ModuleReexports | Module re-exports, if available |
-> Config region |
|
-> Config region | Refined |
Refine a Config
by incorporating given SourceType
, CabalInfo
, and
fixity overrides FixityMap
. You can use detectSourceType
to deduce
SourceType
based on the file extension,
getCabalInfoForSourceFile
to obtain CabalInfo
and
getFixityOverridesForSourceFile
for FixityMap
.
Since: 0.5.3.0
A wrapper for dynamic options.
Cabal info
data CabalSearchResult Source #
The result of searching for a .cabal
file.
Since: 0.5.3.0
CabalNotFound | Cabal file could not be found |
CabalDidNotMention CabalInfo | Cabal file was found, but it did not mention the source file in question |
CabalFound CabalInfo | Cabal file was found and it mentions the source file in question |
Instances
Show CabalSearchResult Source # | |
Defined in Ormolu.Utils.Cabal showsPrec :: Int -> CabalSearchResult -> ShowS # show :: CabalSearchResult -> String # showList :: [CabalSearchResult] -> ShowS # | |
Eq CabalSearchResult Source # | |
Defined in Ormolu.Utils.Cabal (==) :: CabalSearchResult -> CabalSearchResult -> Bool # (/=) :: CabalSearchResult -> CabalSearchResult -> Bool # |
Cabal information of interest to Ormolu.
CabalInfo | |
|
Instances
getCabalInfoForSourceFile Source #
:: MonadIO m | |
=> FilePath | Haskell source file |
-> m CabalSearchResult | Extracted cabal info, if any |
Locate a .cabal
file corresponding to the given Haskell source file
and obtain CabalInfo
from it.
Fixity overrides and module re-exports
data FixityOverrides Source #
Map from the operator name to its FixityInfo
.
Instances
Show FixityOverrides Source # | |
Defined in Ormolu.Fixity.Internal showsPrec :: Int -> FixityOverrides -> ShowS # show :: FixityOverrides -> String # showList :: [FixityOverrides] -> ShowS # | |
Eq FixityOverrides Source # | |
Defined in Ormolu.Fixity.Internal (==) :: FixityOverrides -> FixityOverrides -> Bool # (/=) :: FixityOverrides -> FixityOverrides -> Bool # |
defaultFixityOverrides :: FixityOverrides Source #
Fixity overrides to use by default.
data ModuleReexports Source #
Module re-exports
Instances
Show ModuleReexports Source # | |
Defined in Ormolu.Fixity.Internal showsPrec :: Int -> ModuleReexports -> ShowS # show :: ModuleReexports -> String # showList :: [ModuleReexports] -> ShowS # | |
Eq ModuleReexports Source # | |
Defined in Ormolu.Fixity.Internal (==) :: ModuleReexports -> ModuleReexports -> Bool # (/=) :: ModuleReexports -> ModuleReexports -> Bool # |
defaultModuleReexports :: ModuleReexports Source #
Module re-exports to apply by default.
getDotOrmoluForSourceFile Source #
:: MonadIO m | |
=> FilePath |
|
-> m (FixityOverrides, ModuleReexports) |
Attempt to locate and parse an .ormolu
file. If it does not exist,
default fixity map and module reexports are returned. This function
maintains a cache of fixity overrides and module re-exports where cabal
file paths act as keys.
Working with exceptions
data OrmoluException Source #
Ormolu exception representing all cases when Ormolu can fail.
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 (NonEmpty PError) | 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 | |
Show OrmoluException Source # | |
Defined in Ormolu.Exception showsPrec :: Int -> OrmoluException -> ShowS # show :: OrmoluException -> String # showList :: [OrmoluException] -> ShowS # |
withPrettyOrmoluExceptions Source #
Inside this wrapper OrmoluException
will be caught and displayed
nicely.