1
1
mirror of https://github.com/tweag/ormolu.git synced 2024-09-11 13:16:13 +03:00
ormolu/app/Main.hs

383 lines
12 KiB
Haskell
Raw Normal View History

{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE QuasiQuotes #-}
2019-02-24 23:38:10 +03:00
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
2019-02-24 23:38:10 +03:00
2020-04-24 20:43:45 +03:00
module Main (main) where
2018-11-25 16:34:28 +03:00
import Control.Exception (throwIO)
2019-02-24 23:38:10 +03:00
import Control.Monad
import Data.Bool (bool)
import Data.List (intercalate, sort)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, mapMaybe, maybeToList)
import qualified Data.Set as Set
import qualified Data.Text.IO as TIO
2019-02-24 23:38:10 +03:00
import Data.Version (showVersion)
import Language.Haskell.TH.Env (envQ)
2019-02-24 23:38:10 +03:00
import Options.Applicative
import Ormolu
import Ormolu.Diff.Text (diffText, printTextDiff)
import Ormolu.Fixity (FixityInfo, OpName)
import Ormolu.Parser (manualExts)
import Ormolu.Terminal
import Ormolu.Utils (showOutputable)
import Ormolu.Utils.Fixity (parseFixityDeclarationStr)
import Ormolu.Utils.IO
2019-02-24 23:38:10 +03:00
import Paths_ormolu (version)
import System.Directory
import System.Exit (ExitCode (..), exitWith)
import qualified System.FilePath as FP
2019-07-04 03:52:35 +03:00
import System.IO (hPutStrLn, stderr)
2019-02-24 23:38:10 +03:00
-- | Entry point of the program.
2018-11-25 16:34:28 +03:00
main :: IO ()
main = do
2019-02-24 23:38:10 +03:00
Opts {..} <- execParser optsParserInfo
2021-10-18 17:00:46 +03:00
let formatOne' =
formatOne
optCabal
2021-10-18 17:00:46 +03:00
optMode
optSourceType
optConfig
exitCode <- case optInputFiles of
[] -> formatOne' Nothing
["-"] -> formatOne' Nothing
[x] -> formatOne' (Just x)
xs -> do
let selectFailure = \case
ExitSuccess -> Nothing
ExitFailure n -> Just n
errorCodes <-
mapMaybe selectFailure <$> mapM (formatOne' . Just) (sort xs)
return $
if null errorCodes
then ExitSuccess
else
ExitFailure $
if all (== 100) errorCodes
then 100
else 102
exitWith exitCode
-- | Format a single input.
formatOne ::
-- | How to use .cabal files
CabalOpts ->
-- | Mode of operation
Mode ->
2021-10-18 17:00:46 +03:00
-- | The 'SourceType' requested by the user
Maybe SourceType ->
-- | Configuration
2020-04-23 19:41:32 +03:00
Config RegionIndices ->
-- | File to format or stdin as 'Nothing'
Maybe FilePath ->
IO ExitCode
formatOne CabalOpts {..} mode reqSourceType rawConfig mpath =
2021-10-18 17:00:46 +03:00
withPrettyOrmoluExceptions (cfgColorMode rawConfig) $ do
let getCabalInfoForSourceFile' sourceFile = do
cabalSearchResult <- getCabalInfoForSourceFile sourceFile
let debugEnabled = cfgDebug rawConfig
case cabalSearchResult of
CabalNotFound -> do
when debugEnabled $
hPutStrLn stderr $
"Could not find a .cabal file for " <> sourceFile
return Nothing
CabalDidNotMention cabalInfo -> do
when debugEnabled $ do
relativeCabalFile <-
makeRelativeToCurrentDirectory (ciCabalFilePath cabalInfo)
hPutStrLn stderr $
"Found .cabal file "
<> relativeCabalFile
<> ", but it did not mention "
<> sourceFile
return (Just cabalInfo)
CabalFound cabalInfo -> return (Just cabalInfo)
case FP.normalise <$> mpath of
-- input source = STDIN
Nothing -> do
resultConfig <-
( if optDoNotUseCabal
then pure Nothing
else case optStdinInputFile of
Just stdinInputFile ->
getCabalInfoForSourceFile' stdinInputFile
Nothing -> throwIO OrmoluMissingStdinInputFile
)
>>= patchConfig Nothing
case mode of
Stdout -> do
ormoluStdin resultConfig >>= TIO.putStr
return ExitSuccess
InPlace -> do
hPutStrLn
stderr
"In place editing is not supported when input comes from stdin."
-- 101 is different from all the other exit codes we already use.
return (ExitFailure 101)
Check -> do
-- ormoluStdin is not used because we need the originalInput
originalInput <- getContentsUtf8
let stdinRepr = "<stdin>"
formattedInput <-
2023-01-06 16:42:22 +03:00
ormolu resultConfig stdinRepr originalInput
handleDiff originalInput formattedInput stdinRepr
-- input source = a file
Just inputFile -> do
resultConfig <-
( if optDoNotUseCabal
then pure Nothing
else getCabalInfoForSourceFile' inputFile
)
>>= patchConfig (Just (detectSourceType inputFile))
case mode of
Stdout -> do
ormoluFile resultConfig inputFile >>= TIO.putStr
return ExitSuccess
InPlace -> do
-- ormoluFile is not used because we need originalInput
originalInput <- readFileUtf8 inputFile
2021-10-18 17:00:46 +03:00
formattedInput <-
2023-01-06 16:42:22 +03:00
ormolu resultConfig inputFile originalInput
when (formattedInput /= originalInput) $
writeFileUtf8 inputFile formattedInput
return ExitSuccess
Check -> do
-- ormoluFile is not used because we need originalInput
originalInput <- readFileUtf8 inputFile
2021-10-18 17:00:46 +03:00
formattedInput <-
2023-01-06 16:42:22 +03:00
ormolu resultConfig inputFile originalInput
handleDiff originalInput formattedInput inputFile
where
patchConfig mdetectedSourceType mcabalInfo = do
let sourceType =
fromMaybe
ModuleSource
(reqSourceType <|> mdetectedSourceType)
mfixityOverrides <- traverse getFixityOverridesForSourceFile mcabalInfo
return (refineConfig sourceType mcabalInfo mfixityOverrides rawConfig)
handleDiff originalInput formattedInput fileRepr =
case diffText originalInput formattedInput fileRepr of
Nothing -> return ExitSuccess
Just diff -> do
2021-10-18 17:00:46 +03:00
runTerm (printTextDiff diff) (cfgColorMode rawConfig) stderr
-- 100 is different to all the other exit code that are emitted
-- either from an 'OrmoluException' or from 'error' and
-- 'notImplemented'.
return (ExitFailure 100)
2019-02-24 23:38:10 +03:00
----------------------------------------------------------------------------
-- Command line options parsing
2019-02-24 23:38:10 +03:00
-- | All command line options.
data Opts = Opts
{ -- | Mode of operation
optMode :: !Mode,
-- | Ormolu 'Config'
2020-04-23 19:41:32 +03:00
optConfig :: !(Config RegionIndices),
-- | Options related to info extracted from .cabal files
optCabal :: CabalOpts,
2021-10-18 17:00:46 +03:00
-- | Source type option, where 'Nothing' means autodetection
optSourceType :: !(Maybe SourceType),
-- | Haskell source files to format or stdin (when the list is empty)
optInputFiles :: ![FilePath]
}
2019-02-24 23:38:10 +03:00
-- | Mode of operation.
data Mode
= -- | Output formatted source code to stdout
Stdout
| -- | Overwrite original file
InPlace
| -- | Exit with non-zero status code if
-- source is not already formatted
Check
2019-02-24 23:38:10 +03:00
deriving (Eq, Show)
-- | Configuration related to .cabal files.
data CabalOpts = CabalOpts
{ -- | DO NOT extract default-extensions and dependencies from .cabal files
optDoNotUseCabal :: Bool,
-- | Optional path to a file which will be used to find a .cabal file
-- when using input from stdin
optStdinInputFile :: Maybe FilePath
}
deriving (Show)
2019-02-24 23:38:10 +03:00
optsParserInfo :: ParserInfo Opts
optsParserInfo =
info (helper <*> ver <*> exts <*> optsParser) . mconcat $
[fullDesc]
2019-02-24 23:38:10 +03:00
where
ver :: Parser (a -> a)
ver =
infoOption verStr . mconcat $
[ long "version",
short 'v',
help "Print version of the program"
]
verStr =
intercalate
"\n"
[ unwords $
["ormolu", showVersion version]
<> maybeToList $$(envQ @String "ORMOLU_REV"),
"using ghc-lib-parser " ++ VERSION_ghc_lib_parser
2019-02-24 23:38:10 +03:00
]
exts :: Parser (a -> a)
exts =
infoOption displayExts . mconcat $
[ long "manual-exts",
help "Display extensions that need to be enabled manually"
]
displayExts = unlines $ sort (showOutputable <$> manualExts)
2019-02-24 23:38:10 +03:00
optsParser :: Parser Opts
optsParser =
Opts
<$> ( (fmap (bool Stdout InPlace) . switch . mconcat)
[ short 'i',
help "A shortcut for --mode inplace"
]
<|> (option parseMode . mconcat)
[ long "mode",
short 'm',
metavar "MODE",
value Stdout,
help "Mode of operation: 'stdout' (the default), 'inplace', or 'check'"
]
)
<*> configParser
<*> cabalOptsParser
2021-10-18 17:00:46 +03:00
<*> sourceTypeParser
<*> (many . strArgument . mconcat)
[ metavar "FILE",
help "Haskell source files to format or stdin (the default)"
]
cabalOptsParser :: Parser CabalOpts
cabalOptsParser =
CabalOpts
<$> (switch . mconcat)
[ long "no-cabal",
help $
"Do not extract default-extensions and dependencies from .cabal files"
++ ", do not look for .ormolu files"
]
<*> (optional . strOption . mconcat)
[ long "stdin-input-file",
help "Path which will be used to find the .cabal file when using input from stdin"
]
2020-04-23 19:41:32 +03:00
configParser :: Parser (Config RegionIndices)
configParser =
Config
<$> (fmap (fmap DynOption) . many . strOption . mconcat)
[ long "ghc-opt",
short 'o',
metavar "OPT",
help "GHC options to enable (e.g. language extensions)"
]
<*> ( fmap (Map.fromListWith (<>) . mconcat)
. many
. option parseFixityDeclaration
. mconcat
)
[ long "fixity",
short 'f',
metavar "FIXITY",
help "Fixity declaration to use (an override)"
]
<*> (fmap Set.fromList . many . strOption . mconcat)
[ long "package",
short 'p',
metavar "PACKAGE",
help "Explicitly specified dependency (for operator fixity/precedence only)"
]
<*> (switch . mconcat)
[ long "unsafe",
short 'u',
help "Do formatting faster but without automatic detection of defects"
]
<*> (switch . mconcat)
[ long "debug",
short 'd',
help "Output information useful for debugging"
]
<*> (switch . mconcat)
[ long "check-idempotence",
short 'c',
help "Fail if formatting is not idempotent"
]
2021-10-18 17:00:46 +03:00
-- We cannot parse the source type here, because we might need to do
-- autodection based on the input file extension (not available here)
-- before storing the resolved value in the config struct.
<*> pure ModuleSource
<*> (option parseColorMode . mconcat)
[ long "color",
metavar "WHEN",
value Auto,
help "Colorize the output; WHEN can be 'never', 'always', or 'auto' (the default)"
]
2020-04-23 19:41:32 +03:00
<*> ( RegionIndices
<$> (optional . option auto . mconcat)
[ long "start-line",
metavar "START",
help "Start line of the region to format (starts from 1)"
2020-04-23 19:41:32 +03:00
]
<*> (optional . option auto . mconcat)
[ long "end-line",
metavar "END",
2020-04-23 19:41:32 +03:00
help "End line of the region to format (inclusive)"
]
)
2019-02-24 23:38:10 +03:00
2021-10-18 17:00:46 +03:00
sourceTypeParser :: Parser (Maybe SourceType)
sourceTypeParser =
(option parseSourceType . mconcat)
[ long "source-type",
short 't',
metavar "TYPE",
value Nothing,
help "Set the type of source; TYPE can be 'module', 'sig', or 'auto' (the default)"
]
2019-02-24 23:38:10 +03:00
----------------------------------------------------------------------------
-- Helpers
-- | Parse 'Mode'.
parseMode :: ReadM Mode
parseMode = eitherReader $ \case
"stdout" -> Right Stdout
"inplace" -> Right InPlace
"check" -> Right Check
s -> Left $ "unknown mode: " ++ s
-- | Parse a fixity declaration.
parseFixityDeclaration :: ReadM [(OpName, FixityInfo)]
parseFixityDeclaration = eitherReader parseFixityDeclarationStr
2021-10-18 17:00:46 +03:00
-- | Parse 'ColorMode'.
parseColorMode :: ReadM ColorMode
parseColorMode = eitherReader $ \case
"never" -> Right Never
"always" -> Right Always
"auto" -> Right Auto
s -> Left $ "unknown color mode: " ++ s
2021-10-18 17:00:46 +03:00
-- | Parse the 'SourceType'. 'Nothing' means that autodetection based on
-- file extension is requested.
parseSourceType :: ReadM (Maybe SourceType)
parseSourceType = eitherReader $ \case
"module" -> Right (Just ModuleSource)
"sig" -> Right (Just SignatureSource)
"auto" -> Right Nothing
s -> Left $ "unknown source type: " ++ s