-- |
-- Module: Staversion.Internal.Command
-- Description: Command from the user.
-- Maintainer: Toshio Ito <debug.ito@gmail.com>
--
-- __This is an internal module. End-users should not use it.__
module Staversion.Internal.Command
       ( Command(..),
         parseCommandArgs,
         defFormatConfig,
         _parseCommandStrings
       ) where

import Control.Applicative ((<$>), (<*>), optional, some, (<|>), many)
import Data.Function (on)
import Data.Monoid (mconcat, (<>))
import Data.Text (pack)
import qualified Options.Applicative as Opt
import qualified Paths_staversion as MyInfo
import System.Directory (getHomeDirectory)
import System.FilePath ((</>))
import qualified Text.PrettyPrint.ANSI.Leijen as Pretty

import Staversion.Internal.Aggregate (Aggregator)
import qualified Staversion.Internal.Aggregate as Agg
import Staversion.Internal.Format (FormatConfig(..), FormatVersion)
import qualified Staversion.Internal.Format as Format
import Staversion.Internal.Log
  ( LogLevel(..), Logger(loggerThreshold), defaultLogger
  )
import Staversion.Internal.Query
  ( Resolver,
    PackageName,
    Query(..),
    parseQuery,
    PackageSource(..)
  )
import Staversion.Internal.Version (showBaseVersion)

-- | Command from the user.
data Command =
  Command { Command -> [Char]
commBuildPlanDir :: FilePath,
            -- ^ path to the directory where build plan files are stored.
            Command -> [Char]
commStackCommand :: String,
            -- ^ shell command to invoke @stack@ tool.
            Command -> Logger
commLogger :: Logger,
            -- ^ the logger
            Command -> [PackageSource]
commSources :: [PackageSource],
            -- ^ package sources to search
            Command -> [Query]
commQueries :: [Query],
            -- ^ package queries
            Command -> Bool
commAllowNetwork :: Bool,
            -- ^ if 'True', it accesses the Internet to query build plans etc.
            Command -> Maybe Aggregator
commAggregator :: Maybe Aggregator,
            -- ^ if 'Just', do aggregation over the results.
            Command -> FormatConfig
commFormatConfig :: FormatConfig
            -- ^ config for the formatter
          }

-- | Default values for 'Command'.
data DefCommand = DefCommand { DefCommand -> [Char]
defBuildPlanDir :: FilePath
                             } deriving (Int -> DefCommand -> ShowS
[DefCommand] -> ShowS
DefCommand -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DefCommand] -> ShowS
$cshowList :: [DefCommand] -> ShowS
show :: DefCommand -> [Char]
$cshow :: DefCommand -> [Char]
showsPrec :: Int -> DefCommand -> ShowS
$cshowsPrec :: Int -> DefCommand -> ShowS
Show,DefCommand -> DefCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefCommand -> DefCommand -> Bool
$c/= :: DefCommand -> DefCommand -> Bool
== :: DefCommand -> DefCommand -> Bool
$c== :: DefCommand -> DefCommand -> Bool
Eq,Eq DefCommand
DefCommand -> DefCommand -> Bool
DefCommand -> DefCommand -> Ordering
DefCommand -> DefCommand -> DefCommand
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefCommand -> DefCommand -> DefCommand
$cmin :: DefCommand -> DefCommand -> DefCommand
max :: DefCommand -> DefCommand -> DefCommand
$cmax :: DefCommand -> DefCommand -> DefCommand
>= :: DefCommand -> DefCommand -> Bool
$c>= :: DefCommand -> DefCommand -> Bool
> :: DefCommand -> DefCommand -> Bool
$c> :: DefCommand -> DefCommand -> Bool
<= :: DefCommand -> DefCommand -> Bool
$c<= :: DefCommand -> DefCommand -> Bool
< :: DefCommand -> DefCommand -> Bool
$c< :: DefCommand -> DefCommand -> Bool
compare :: DefCommand -> DefCommand -> Ordering
$ccompare :: DefCommand -> DefCommand -> Ordering
Ord)

defCommand :: IO DefCommand
defCommand :: IO DefCommand
defCommand = [Char] -> DefCommand
DefCommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [Char]
def_build_plan_dir where
  def_build_plan_dir :: IO [Char]
def_build_plan_dir = do
    [Char]
home <- IO [Char]
getHomeDirectory
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Char]
home [Char] -> ShowS
</> [Char]
".stack" [Char] -> ShowS
</> [Char]
"build-plan"

commandParser :: DefCommand -> Opt.Parser Command
commandParser :: DefCommand -> Parser Command
commandParser DefCommand
def_comm = [Char]
-> [Char]
-> Logger
-> [PackageSource]
-> [Query]
-> Bool
-> Maybe Aggregator
-> FormatConfig
-> Command
Command forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [Char]
build_plan_dir forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Char]
stack_command forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Logger
logger forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [PackageSource]
sources
                         forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Query]
queries forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
network forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Aggregator)
aggregate forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FormatConfig
format_config where
  logger :: Parser Logger
logger = Bool -> Logger
makeLogger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
is_verbose
  makeLogger :: Bool -> Logger
makeLogger Bool
True = Logger
defaultLogger { loggerThreshold :: Maybe LogLevel
loggerThreshold = forall a. a -> Maybe a
Just LogLevel
LogDebug }
  makeLogger Bool
False = Logger
defaultLogger
  is_verbose :: Parser Bool
is_verbose = Mod FlagFields Bool -> Parser Bool
Opt.switch forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"verbose",
                                      forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'v',
                                      forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Verbose messages."
                                    ]
  build_plan_dir :: Parser [Char]
build_plan_dir = forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption
                   forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"build-plan-dir",
                               forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Directory where build plan YAML files are stored.",
                               forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"DIR",
                               forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value (DefCommand -> [Char]
defBuildPlanDir DefCommand
def_comm),
                               forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
                             ]
  withDefault :: Functor m => [a] -> m [a] -> m [a]
  withDefault :: forall (m :: * -> *) a. Functor m => [a] -> m [a] -> m [a]
withDefault [a]
def_vals = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> [a]
applyDef
    where
      applyDef :: [a] -> [a]
applyDef [] = [a]
def_vals
      applyDef [a]
vs = [a]
vs
  sources :: Parser [PackageSource]
sources = forall (m :: * -> *) a. Functor m => [a] -> m [a] -> m [a]
withDefault [PackageSource
SourceStackDefault] forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall a b. (a -> b) -> a -> b
$ Parser PackageSource
resolver forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser PackageSource
hackage forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser PackageSource
stack_explicit forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser PackageSource
stack_default
  resolver :: Parser PackageSource
resolver = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> PackageSource
SourceStackage forall a b. (a -> b) -> a -> b
$ forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption
             forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"resolver",
                         forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'r',
                         forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Stackage resolver to search. e.g. \"lts-6.15\"",
                         forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"RESOLVER_NAME"
                       ]
  hackage :: Parser PackageSource
hackage = forall a. a -> Mod FlagFields a -> Parser a
Opt.flag' PackageSource
SourceHackage
            forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"hackage",
                        forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'H',
                        forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Search hackage.org for the latest version."
                      ]
  stack_explicit :: Parser PackageSource
stack_explicit = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> PackageSource
SourceStackYaml forall a b. (a -> b) -> a -> b
$ forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption
                   forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"stack",
                               forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help ( [Char]
"Path to stack.yaml file."
                                          forall a. [a] -> [a] -> [a]
++ [Char]
" It searches for package versions of the resolver of the specified stack.yaml file."
                                        ),
                               forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"FILE"
                             ]
  stack_default :: Parser PackageSource
stack_default = forall a. a -> Mod FlagFields a -> Parser a
Opt.flag' PackageSource
SourceStackDefault
                  forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"stack-default",
                              forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'S',
                              forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help ( [Char]
"Search the resolver that 'stack' command would use by default."
                                         forall a. [a] -> [a] -> [a]
++ [Char]
" This option is implied if there is no options about package source (e.g. -r and -H)."
                                       )
                            ]
  queries :: Parser [Query]
queries = forall (m :: * -> *) a. Functor m => [a] -> m [a] -> m [a]
withDefault [Query
QueryStackYamlDefault] forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall a b. (a -> b) -> a -> b
$ [Char] -> Query
parseQuery forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser [Char]
query_package forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser [Char]
query_cabal forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser [Char]
query_stack_yaml)
  query_package :: Parser [Char]
query_package = forall s. IsString s => Mod ArgumentFields s -> Parser s
Opt.strArgument
                  forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Name of package whose version you want to check.",
                              forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"PACKAGE_NAME"
                            ]
  query_cabal :: Parser [Char]
query_cabal = forall s. IsString s => Mod ArgumentFields s -> Parser s
Opt.strArgument
                forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
".cabal file name. It checks versions of packages in build-deps lists.",
                            forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"CABAL_FILEPATH"
                          ]
  query_stack_yaml :: Parser [Char]
query_stack_yaml = forall s. IsString s => Mod ArgumentFields s -> Parser s
Opt.strArgument
                     forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help ( [Char]
"Path to stack.yaml file."
                                            forall a. [a] -> [a] -> [a]
++ [Char]
" It checks versions of packages in build-deps of all cabal projects listed in the stack.yaml."
                                            forall a. [a] -> [a] -> [a]
++ [Char]
" If you just type 'stack.yaml',"
                                            forall a. [a] -> [a] -> [a]
++ [Char]
" it means the default configuration that 'stack' command would use by default."
                                            forall a. [a] -> [a] -> [a]
++ [Char]
" 'stack.yaml' is implied if there is no query argument."
                                          ),
                                 forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"STACK_YAML_FILEPATH"
                               ]
  network :: Parser Bool
network = Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
no_network
  no_network :: Parser Bool
no_network = Mod FlagFields Bool -> Parser Bool
Opt.switch forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"no-network",
                                      forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Forbid network access."
                                    ]
  aggregate :: Parser (Maybe Aggregator)
aggregate = forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$ forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option (forall a. [Char] -> ([Char] -> Maybe a) -> ReadM a
maybeReader [Char]
"AGGREGATOR" [Char] -> Maybe Aggregator
parseAggregator)
              forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"aggregate",
                          forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'a',
                          forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"AGGREGATOR",
                          forall (f :: * -> *) a. Maybe Doc -> Mod f a
Opt.helpDoc forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Char] -> Doc
docAggregators [Char]
"AGGREGATOR"
                        ]
  format_config :: Parser FormatConfig
format_config = FormatVersion -> FormatConfig
FormatConfig forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser FormatVersion
format_version
  format_version :: Parser FormatVersion
format_version = forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option (forall a. [Char] -> ([Char] -> Maybe a) -> ReadM a
maybeReader [Char]
"FORMAT" forall a b. (a -> b) -> a -> b
$ forall a. [SelectSpec a] -> [Char] -> Maybe a
parseSelect [SelectSpec FormatVersion]
formatVersions)
                   forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"format-version",
                               forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"FORMAT",
                               forall (f :: * -> *) a. Maybe Doc -> Mod f a
Opt.helpDoc forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Char] -> Doc
docFormatVersions [Char]
"FORMAT",
                               forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value forall a b. (a -> b) -> a -> b
$ FormatConfig -> FormatVersion
fconfFormatVersion FormatConfig
defFormatConfig
                             ]
  stack_command :: Parser [Char]
stack_command = forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption
                  forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"stack-command",
                              forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Shell command for stack tool.",
                              forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"COMMAND",
                              forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value [Char]
"stack",
                              forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
                            ]

maybeReader :: String -> (String -> Maybe a) -> Opt.ReadM a
maybeReader :: forall a. [Char] -> ([Char] -> Maybe a) -> ReadM a
maybeReader [Char]
metavar [Char] -> Maybe a
mfunc = do
  [Char]
got <- forall s. IsString s => ReadM s
Opt.str
  case [Char] -> Maybe a
mfunc [Char]
got of
   Maybe a
Nothing -> forall a. [Char] -> ReadM a
Opt.readerError ([Char]
"Unknown " forall a. [a] -> [a] -> [a]
++ [Char]
metavar forall a. [a] -> [a] -> [a]
++ [Char]
": " forall a. [a] -> [a] -> [a]
++ [Char]
got)
   Just a
v -> forall (m :: * -> *) a. Monad m => a -> m a
return a
v


data SelectSpec a = SelectSpec { forall a. SelectSpec a -> a
selectResult :: a,
                                 forall a. SelectSpec a -> [Char]
selectSymbol :: String,
                                 forall a. SelectSpec a -> [Char]
selectDesc :: String
                               }

type AggregatorSpec = SelectSpec Aggregator

aggregators :: [AggregatorSpec]
aggregators :: [AggregatorSpec]
aggregators = [ forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec Aggregator
Agg.aggOr [Char]
"or" [Char]
"concatenate versions with (||).",
                forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec Aggregator
Agg.aggPvpMajor [Char]
"pvp-major"
                ( [Char]
"aggregate versions to a range that is supposed to be "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"compatible with the given versions "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"in terms of PVP (Package Versioning Policy.) "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"Major versions are used for upper bounds."
                ),
                forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec Aggregator
Agg.aggPvpMajor [Char]
"pvp" [Char]
"alias for 'pvp-major'",
                forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec Aggregator
Agg.aggPvpMinor [Char]
"pvp-minor"
                ( [Char]
"aggregate versions to a range that is supposed to be "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"compatible with the given versions "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"in terms of PVP. "
                  forall a. [a] -> [a] -> [a]
++ [Char]
"Minor versions are used for upper bounds, i.e. this is stricter than 'pvp-major'."
                )
              ]

parseSelect :: [SelectSpec a] -> String -> Maybe a
parseSelect :: forall a. [SelectSpec a] -> [Char] -> Maybe a
parseSelect [SelectSpec a]
specs [Char]
symbol = forall {a}. [SelectSpec a] -> Maybe a
toMaybe forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (\SelectSpec a
spec -> forall a. SelectSpec a -> [Char]
selectSymbol SelectSpec a
spec forall a. Eq a => a -> a -> Bool
== [Char]
symbol) [SelectSpec a]
specs where
  toMaybe :: [SelectSpec a] -> Maybe a
toMaybe [] = forall a. Maybe a
Nothing
  toMaybe (SelectSpec a
spec : [SelectSpec a]
_) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. SelectSpec a -> a
selectResult SelectSpec a
spec

parseAggregator :: String -> Maybe Aggregator
parseAggregator :: [Char] -> Maybe Aggregator
parseAggregator = forall a. [SelectSpec a] -> [Char] -> Maybe a
parseSelect [AggregatorSpec]
aggregators

wrapped :: String -> Pretty.Doc
wrapped :: [Char] -> Doc
wrapped = [Doc] -> Doc
Pretty.fillSep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Doc
Pretty.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
words

docSelect :: [SelectSpec a] -> String -> String -> Pretty.Doc
docSelect :: forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelect [SelectSpec a]
specs [Char]
foreword_str [Char]
metavar = [Doc] -> Doc
Pretty.vsep forall a b. (a -> b) -> a -> b
$ (Doc
foreword  forall a. a -> [a] -> [a]
:) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a}. SelectSpec a -> Doc
docSpec [SelectSpec a]
specs where
  foreword :: Doc
foreword = [Char] -> Doc
wrapped ( [Char]
foreword_str forall a. [a] -> [a] -> [a]
++ [Char]
" Possible " forall a. [a] -> [a] -> [a]
++ [Char]
metavar forall a. [a] -> [a] -> [a]
++ [Char]
" is:" )
  docSpec :: SelectSpec a -> Doc
docSpec SelectSpec {selectSymbol :: forall a. SelectSpec a -> [Char]
selectSymbol = [Char]
symbol, selectDesc :: forall a. SelectSpec a -> [Char]
selectDesc = [Char]
desc} =
    Int -> Doc -> Doc
Pretty.hang Int
2 forall a b. (a -> b) -> a -> b
$ [Char] -> Doc
wrapped ([Char]
symbol forall a. Semigroup a => a -> a -> a
<> [Char]
": " forall a. Semigroup a => a -> a -> a
<> [Char]
desc)

docSelectWithDefault :: [SelectSpec a] -> String -> String -> Pretty.Doc
docSelectWithDefault :: forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelectWithDefault [] [Char]
foreword [Char]
metavar = forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelect [] [Char]
foreword [Char]
metavar where
docSelectWithDefault (SelectSpec a
def_spec : [SelectSpec a]
rest) [Char]
foreword [Char]
metavar = forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelect (SelectSpec a
def_spec' forall a. a -> [a] -> [a]
: [SelectSpec a]
rest) [Char]
foreword [Char]
metavar where
  def_spec' :: SelectSpec a
def_spec' = SelectSpec a
def_spec { selectSymbol :: [Char]
selectSymbol = forall a. SelectSpec a -> [Char]
selectSymbol SelectSpec a
def_spec forall a. Semigroup a => a -> a -> a
<> [Char]
" [DEFAULT]" }
  

docAggregators :: String -> Pretty.Doc
docAggregators :: [Char] -> Doc
docAggregators = forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelect [AggregatorSpec]
aggregators [Char]
"Aggregate version results over different resolvers."


defFormatConfig :: FormatConfig
defFormatConfig :: FormatConfig
defFormatConfig = FormatConfig { fconfFormatVersion :: FormatVersion
fconfFormatVersion = forall a. SelectSpec a -> a
selectResult forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head [SelectSpec FormatVersion]
formatVersions
                               }

formatVersions :: [SelectSpec FormatVersion]
formatVersions :: [SelectSpec FormatVersion]
formatVersions = [ forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec FormatVersion
Format.formatVersionCabal [Char]
"cabal"
                   ( [Char]
"Let Cabal format VersionRanges"
                   ),
                   forall a. a -> [Char] -> [Char] -> SelectSpec a
SelectSpec FormatVersion
Format.formatVersionCabalCaret [Char]
"cabal-caret"
                   ( [Char]
"Similar to 'cabal', but it uses the caret operator (^>=) if possible"
                   )
                 ]


docFormatVersions :: String -> Pretty.Doc
docFormatVersions :: [Char] -> Doc
docFormatVersions = forall a. [SelectSpec a] -> [Char] -> [Char] -> Doc
docSelectWithDefault [SelectSpec FormatVersion]
formatVersions [Char]
"Format for package version ranges."

programDescription :: Opt.Parser a -> Opt.ParserInfo a
programDescription :: forall a. Parser a -> ParserInfo a
programDescription Parser a
parser =
  forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (forall a. Parser (a -> a)
Opt.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser a
parser)
  forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [ forall a. InfoMod a
Opt.fullDesc,
              forall a. [Char] -> InfoMod a
Opt.progDesc ( [Char]
"Look for version numbers for Haskell packages in specific stackage resolvers"
                             forall a. [a] -> [a] -> [a]
++ [Char]
" (or possibly other package sources)"
                           ),
              forall a. [Char] -> InfoMod a
Opt.footer ([Char]
"Version: " forall a. [a] -> [a] -> [a]
++ (BaseVersion -> [Char]
showBaseVersion BaseVersion
MyInfo.version))
            ]

parseCommandArgs :: IO Command
parseCommandArgs :: IO Command
parseCommandArgs = forall a. ParserInfo a -> IO a
Opt.execParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Parser a -> ParserInfo a
programDescription forall b c a. (b -> c) -> (a -> b) -> a -> c
. DefCommand -> Parser Command
commandParser forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO DefCommand
defCommand

-- | Just for testing.
_parseCommandStrings :: [String] -> IO (Maybe Command)
_parseCommandStrings :: [[Char]] -> IO (Maybe Command)
_parseCommandStrings [[Char]]
args = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall {a}. ParserInfo a -> Maybe a
doParse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Parser a -> ParserInfo a
programDescription forall b c a. (b -> c) -> (a -> b) -> a -> c
. DefCommand -> Parser Command
commandParser) IO DefCommand
defCommand
  where
    doParse :: ParserInfo a -> Maybe a
doParse ParserInfo a
pinfo = forall a. ParserResult a -> Maybe a
Opt.getParseResult forall a b. (a -> b) -> a -> b
$ forall a. ParserPrefs -> ParserInfo a -> [[Char]] -> ParserResult a
Opt.execParserPure ParserPrefs
prefs ParserInfo a
pinfo [[Char]]
args
    prefs :: ParserPrefs
prefs = PrefsMod -> ParserPrefs
Opt.prefs forall a. Monoid a => a
mempty