{-# LANGUAGE NoImplicitPrelude #-}

module Stack.Options.SDistParser
 ( sdistOptsParser
 ) where

import           Options.Applicative
import           Options.Applicative.Builder.Extra
import           Stack.Prelude
import           Stack.SDist
import           Stack.Options.HpcReportParser ( pvpBoundsOption )

-- | Parser for arguments to `stack sdist`

sdistOptsParser :: Parser SDistOpts
sdistOptsParser :: Parser SDistOpts
sdistOptsParser = [String]
-> Maybe PvpBounds -> Bool -> Bool -> Maybe String -> SDistOpts
SDistOpts
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument
        (  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"DIR"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer Completer
dirCompleter
        ))
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser PvpBounds
pvpBoundsOption
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
ignoreCheckSwitch
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
buildPackageOption
  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (forall s. IsString s => Mod OptionFields s -> Parser s
strOption
        (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"tar-dir"
        forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"If specified, copy all the tar to this dir"
        ))
 where
  ignoreCheckSwitch :: Parser Bool
ignoreCheckSwitch = Mod FlagFields Bool -> Parser Bool
switch
    (  forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"ignore-check"
    forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. String -> Mod f a
help String
"Do not check package for common mistakes"
    )
  buildPackageOption :: Parser Bool
buildPackageOption = Bool -> String -> String -> Mod FlagFields Bool -> Parser Bool
boolFlags Bool
False
    String
"test-tarball"
    String
"building of the resulting tarball"
    forall m. Monoid m => m
idm