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

157 lines
4.2 KiB
Haskell
Raw Normal View History

2019-02-24 23:38:10 +03:00
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
2018-11-25 16:34:28 +03:00
module Main (main) where
2019-02-24 23:38:10 +03:00
import Control.Monad
import Data.List (intercalate)
import Data.Version (showVersion)
import Development.GitRev
import Options.Applicative
import Ormolu
import Ormolu.Parser (manualExts)
import Ormolu.Utils (showOutputable)
2019-02-24 23:38:10 +03:00
import Paths_ormolu (version)
import System.Exit (ExitCode (..), exitWith)
2019-07-04 03:52:35 +03:00
import System.IO (hPutStrLn, stderr)
import qualified Data.Text.IO as TIO
2019-02-24 23:38:10 +03:00
-- | Entry point of the program.
2018-11-25 16:34:28 +03:00
main :: IO ()
main = withPrettyOrmoluExceptions $ do
2019-02-24 23:38:10 +03:00
Opts {..} <- execParser optsParserInfo
2019-07-04 03:52:35 +03:00
r <- case optInputFile of
2019-07-07 13:29:59 +03:00
"-" -> ormoluStdin optConfig
inputFile -> ormoluFile optConfig inputFile
2019-07-04 03:52:35 +03:00
let notForStdin = do
when (optInputFile == "-") $ do
hPutStrLn
stderr
"This feature is not supported when input comes from stdin."
-- 101 is different from all the other exit codes we already use.
exitWith (ExitFailure 101)
2019-02-24 23:38:10 +03:00
case optMode of
Stdout ->
TIO.putStr r
2019-07-04 03:52:35 +03:00
InPlace -> do
notForStdin
2019-02-24 23:38:10 +03:00
TIO.writeFile optInputFile r
Check -> do
2019-07-04 03:52:35 +03:00
notForStdin
2019-02-24 23:38:10 +03:00
r' <- TIO.readFile optInputFile
2019-07-04 03:52:35 +03:00
when (r /= r') $
-- 100 is different to all the other exit code that are emitted
-- either from an 'OrmoluException' or from 'error' and
-- 'notImplemented'.
exitWith (ExitFailure 100)
2019-02-24 23:38:10 +03:00
----------------------------------------------------------------------------
-- Command line options parsing.
data Opts = Opts
{ optMode :: !Mode
-- ^ Mode of operation
, optConfig :: !Config
-- ^ Ormolu 'Config'
2019-02-24 23:38:10 +03:00
, optInputFile :: !FilePath
2019-07-04 03:52:35 +03:00
-- ^ Input source file or stdin ("-")
2019-02-24 23:38:10 +03:00
}
-- | Mode of operation.
data Mode
= Stdout -- ^ Output formatted source code to stdout
| InPlace -- ^ Overwrite original file
| Check -- ^ Exit with non-zero status code if
-- source is not already formatted
deriving (Eq, Show)
optsParserInfo :: ParserInfo Opts
optsParserInfo = info (helper <*> ver <*> exts <*> optsParser) . mconcat $
2019-02-24 23:38:10 +03:00
[ fullDesc
, progDesc ""
, header ""
]
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
, $gitBranch
, $gitHash
]
, "using ghc " ++ VERSION_ghc
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 (showOutputable <$> manualExts)
2019-02-24 23:38:10 +03:00
optsParser :: Parser Opts
optsParser = Opts
<$> (option parseMode . mconcat)
[ long "mode"
, short 'm'
, metavar "MODE"
, value Stdout
, help "Mode of operation: 'stdout', 'inplace', or 'check'"
]
<*> configParser
<*> (strArgument . mconcat)
[ metavar "FILE"
2019-07-04 03:52:35 +03:00
, value "-"
, help "Haskell source file to format or stdin (default)"
2019-02-24 23:38:10 +03:00
]
configParser :: Parser Config
configParser = Config
<$> (fmap (fmap DynOption) . many . strOption . mconcat)
2019-02-24 23:38:10 +03:00
[ long "ghc-opt"
, short 'o'
, metavar "OPT"
, help "GHC options to enable (e.g. language extensions)"
]
<*> (switch . mconcat)
[ long "unsafe"
, short 'u'
, help "Do formatting faster but without automatic detection of defects"
]
2019-02-24 23:38:10 +03:00
<*> (switch . mconcat)
[ long "debug"
, short 'd'
, help "Output information useful for debugging"
]
2019-07-14 14:05:35 +03:00
<*> (switch . mconcat)
[ long "tolerate-cpp"
, short 'p'
, help "Do not fail if CPP pragma is present"
]
2019-08-16 12:40:15 +03:00
<*> (switch . mconcat)
[ long "check-idempotency"
, short 'c'
, help "Fail if formatting is not idempotent."
]
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