| Safe Haskell | None |
|---|---|
| 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]
- cfgUnsafe :: !Bool
- cfgDebug :: !Bool
- cfgCheckIdempotence :: !Bool
- cfgColorMode :: !ColorMode
- cfgRegion :: !region
- data ColorMode
- data RegionIndices = RegionIndices {
- regionStartLine :: !(Maybe Int)
- regionEndLine :: !(Maybe Int)
- defaultConfig :: Config RegionIndices
- newtype DynOption = DynOption {}
- data OrmoluException
- 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.
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
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>"
Ormolu configuration.
Constructors
| Config | |
Fields
| |
Whether to use colors and other features of ANSI terminals.
Instances
data RegionIndices Source #
Region selection as the combination of start and end line numbers.
Constructors
| RegionIndices | |
Fields
| |
Instances
| Eq RegionIndices Source # | |
Defined in Ormolu.Config Methods (==) :: RegionIndices -> RegionIndices -> Bool # (/=) :: RegionIndices -> RegionIndices -> Bool # | |
| Show RegionIndices Source # | |
Defined in Ormolu.Config Methods showsPrec :: Int -> RegionIndices -> ShowS # show :: RegionIndices -> String # showList :: [RegionIndices] -> ShowS # | |
defaultConfig :: Config RegionIndices Source #
Default .Config RegionIndices
A wrapper for dynamic options.
Constructors
| DynOption | |
Fields | |
Instances
| Eq DynOption Source # | |
| Ord DynOption Source # | |
| Show DynOption Source # | |
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 TextDiff | Formatted source code is not idempotent |
| OrmoluUnrecognizedOpts (NonEmpty String) | Some GHC options were not recognized |
Instances
| Eq OrmoluException Source # | |
Defined in Ormolu.Exception Methods (==) :: OrmoluException -> OrmoluException -> Bool # (/=) :: OrmoluException -> OrmoluException -> Bool # | |
| Show OrmoluException Source # | |
Defined in Ormolu.Exception Methods showsPrec :: Int -> OrmoluException -> ShowS # show :: OrmoluException -> String # showList :: [OrmoluException] -> ShowS # | |
| Exception OrmoluException Source # | |
Defined in Ormolu.Exception Methods toException :: OrmoluException -> SomeException # | |
withPrettyOrmoluExceptions Source #
Inside this wrapper OrmoluException will be caught and displayed
nicely.