2015-12-09 22:13:58 +00:00
|
|
|
-- ghc-mod: Making Haskell development *more* fun
|
|
|
|
-- Copyright (C) 2015 Nikolay Yakimov <root@livid.pp.ru>
|
|
|
|
--
|
|
|
|
-- This program is free software: you can redistribute it and/or modify
|
|
|
|
-- it under the terms of the GNU Affero General Public License as published by
|
|
|
|
-- the Free Software Foundation, either version 3 of the License, or
|
|
|
|
-- (at your option) any later version.
|
|
|
|
--
|
|
|
|
-- This program is distributed in the hope that it will be useful,
|
|
|
|
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
-- GNU Affero General Public License for more details.
|
|
|
|
--
|
|
|
|
-- You should have received a copy of the GNU Affero General Public License
|
|
|
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
2015-12-20 10:50:12 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
2015-12-09 22:13:58 +00:00
|
|
|
|
2015-12-05 20:55:12 +00:00
|
|
|
module GHCMod.Options (
|
|
|
|
parseArgs,
|
2015-12-20 01:22:17 +00:00
|
|
|
parseArgsInteractive,
|
2015-12-05 20:55:12 +00:00
|
|
|
GhcModCommands(..)
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Options.Applicative
|
|
|
|
import Options.Applicative.Types
|
|
|
|
import Language.Haskell.GhcMod.Types
|
|
|
|
import Control.Arrow
|
|
|
|
import GHCMod.Options.Commands
|
|
|
|
import GHCMod.Version
|
2015-12-06 16:22:21 +00:00
|
|
|
import GHCMod.Options.DocUtils
|
2015-12-20 10:50:12 +00:00
|
|
|
import GHCMod.Options.Help
|
2015-12-20 05:26:49 +00:00
|
|
|
import GHCMod.Options.ShellParse
|
2015-12-05 20:55:12 +00:00
|
|
|
|
|
|
|
parseArgs :: IO (Options, GhcModCommands)
|
|
|
|
parseArgs =
|
|
|
|
execParser opts
|
|
|
|
where
|
|
|
|
opts = info (argAndCmdSpec <**> helpVersion)
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ fullDesc
|
|
|
|
<=> header "ghc-mod: Happy Haskell Programming"
|
2015-12-05 20:55:12 +00:00
|
|
|
|
2015-12-20 03:41:34 +00:00
|
|
|
parseArgsInteractive :: String -> Maybe GhcModCommands
|
2015-12-20 01:22:17 +00:00
|
|
|
parseArgsInteractive args =
|
2015-12-20 03:05:43 +00:00
|
|
|
getParseResult $ execParserPure (prefs idm) opts $ parseCmdLine args
|
2015-12-20 01:22:17 +00:00
|
|
|
where
|
|
|
|
opts = info interactiveCommandsSpec $$ fullDesc
|
|
|
|
|
2015-12-05 20:55:12 +00:00
|
|
|
helpVersion :: Parser (a -> a)
|
|
|
|
helpVersion =
|
2015-12-06 16:22:21 +00:00
|
|
|
helper
|
|
|
|
<*> abortOption (InfoMsg ghcModVersion)
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "version"
|
|
|
|
<=> help "Print the version of the program."
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> argument r
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ value id
|
|
|
|
<=> metavar ""
|
2015-12-05 20:55:12 +00:00
|
|
|
where
|
|
|
|
r :: ReadM (a -> a)
|
|
|
|
r = do
|
|
|
|
v <- readerAsk
|
|
|
|
case v of
|
|
|
|
"help" -> readerAbort ShowHelpText
|
|
|
|
"version" -> readerAbort $ InfoMsg ghcModVersion
|
|
|
|
_ -> return id
|
|
|
|
|
|
|
|
argAndCmdSpec :: Parser (Options, GhcModCommands)
|
|
|
|
argAndCmdSpec = (,) <$> globalArgSpec <*> commandsSpec
|
|
|
|
|
|
|
|
splitOn :: Eq a => a -> [a] -> ([a], [a])
|
|
|
|
splitOn c = second (drop 1) . break (==c)
|
|
|
|
|
|
|
|
getLogLevel :: Int -> GmLogLevel
|
|
|
|
getLogLevel = toEnum . min 7
|
|
|
|
|
|
|
|
logLevelParser :: Parser GmLogLevel
|
|
|
|
logLevelParser =
|
2015-12-06 16:22:21 +00:00
|
|
|
getLogLevel
|
|
|
|
<$> silentSwitch
|
|
|
|
<||> logLevelSwitch
|
|
|
|
<||> logLevelOption
|
2015-12-05 20:55:12 +00:00
|
|
|
where
|
|
|
|
logLevelOption =
|
2015-12-06 16:22:21 +00:00
|
|
|
option int
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "verbose"
|
|
|
|
<=> metavar "LEVEL"
|
|
|
|
<=> value 4
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "Set log level. (0-7)"
|
2015-12-05 20:55:12 +00:00
|
|
|
logLevelSwitch =
|
2015-12-06 16:22:21 +00:00
|
|
|
(4+) . length <$> many $$ flag' ()
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ short 'v'
|
|
|
|
<=> help "Increase log level"
|
2015-12-06 16:22:21 +00:00
|
|
|
silentSwitch = flag' 0
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "silent"
|
|
|
|
<=> short 's'
|
|
|
|
<=> help "Be silent, set log level to 0"
|
2015-12-05 20:55:12 +00:00
|
|
|
|
|
|
|
outputOptsSpec :: Parser OutputOpts
|
2015-12-06 16:22:21 +00:00
|
|
|
outputOptsSpec = OutputOpts
|
|
|
|
<$> logLevelParser
|
|
|
|
<*> flag PlainStyle LispStyle
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "tolisp"
|
|
|
|
<=> short 'l'
|
|
|
|
<=> help "Format output as an S-Expression"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> LineSeparator <$$> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "boundary"
|
|
|
|
<=> long "line-separator"
|
|
|
|
<=> short 'b'
|
|
|
|
<=> metavar "SEP"
|
|
|
|
<=> value "\0"
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "Output line separator"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> optional $$ splitOn ',' <$$> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "line-prefix"
|
|
|
|
<=> metavar "OUT,ERR"
|
|
|
|
<=> help "Output prefixes"
|
2015-12-05 20:55:12 +00:00
|
|
|
|
|
|
|
programsArgSpec :: Parser Programs
|
2015-12-06 16:22:21 +00:00
|
|
|
programsArgSpec = Programs
|
|
|
|
<$> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "with-ghc"
|
|
|
|
<=> value "ghc"
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "GHC executable to use"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "with-ghc-pkg"
|
|
|
|
<=> value "ghc-pkg"
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "ghc-pkg executable to use (only needed when guessing from GHC path fails)"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "with-cabal"
|
|
|
|
<=> value "cabal"
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "cabal-install executable to use"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "with-stack"
|
|
|
|
<=> value "stack"
|
|
|
|
<=> showDefault
|
|
|
|
<=> help "stack executable to use"
|
2015-12-05 20:55:12 +00:00
|
|
|
|
|
|
|
globalArgSpec :: Parser Options
|
2015-12-06 16:22:21 +00:00
|
|
|
globalArgSpec = Options
|
|
|
|
<$> outputOptsSpec
|
|
|
|
<*> programsArgSpec
|
|
|
|
<*> many $$ strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "ghcOpt"
|
|
|
|
<=> long "ghc-option"
|
|
|
|
<=> short 'g'
|
|
|
|
<=> metavar "OPT"
|
|
|
|
<=> help "Option to be passed to GHC"
|
2015-12-06 16:22:21 +00:00
|
|
|
<*> many fileMappingSpec
|
2015-12-05 20:55:12 +00:00
|
|
|
where
|
|
|
|
fileMappingSpec =
|
2015-12-06 16:22:21 +00:00
|
|
|
getFileMapping . splitOn '=' <$> strOption
|
2015-12-06 18:30:03 +00:00
|
|
|
$$ long "map-file"
|
|
|
|
<=> metavar "MAPPING"
|
2015-12-20 10:50:12 +00:00
|
|
|
<=> fileMappingHelp
|
|
|
|
fileMappingHelp = help' $ do
|
|
|
|
"Redirect one file to another"
|
|
|
|
"--map-file \"file1.hs=file2.hs\""
|
|
|
|
indent 4 $ do
|
|
|
|
"can be used to tell ghc-mod"
|
|
|
|
\\ "that it should take source code"
|
|
|
|
\\ "for `file1.hs` from `file2.hs`."
|
|
|
|
"`file1.hs` can be either full path,"
|
|
|
|
\\ "or path relative to project root."
|
|
|
|
"`file2.hs` has to be either relative to project root,"
|
|
|
|
\\ "or full path (preferred)"
|
|
|
|
"--map-file \"file.hs\""
|
|
|
|
indent 4 $ do
|
|
|
|
"can be used to tell ghc-mod that it should take"
|
|
|
|
\\ "source code for `file.hs` from stdin. File end"
|
|
|
|
\\ "marker is `\\n\\EOT\\n`, i.e. `\\x0A\\x04\\x0A`."
|
|
|
|
\\ "`file.hs` may or may not exist, and should be"
|
|
|
|
\\ "either full path, or relative to project root."
|
2015-12-05 20:55:12 +00:00
|
|
|
getFileMapping = second (\i -> if null i then Nothing else Just i)
|