mirror of
https://github.com/ilyakooo0/optparse-applicative.git
synced 2024-12-11 06:11:50 +03:00
Add module export lists.
This commit is contained in:
parent
0c203e5235
commit
6950f44a19
@ -1,5 +1,16 @@
|
|||||||
{-# LANGUAGE Rank2Types, PatternGuards #-}
|
{-# LANGUAGE Rank2Types, PatternGuards #-}
|
||||||
module Options.Applicative where
|
module Options.Applicative (
|
||||||
|
Parser,
|
||||||
|
|
||||||
|
ParserInfo(..),
|
||||||
|
info,
|
||||||
|
|
||||||
|
evalParser,
|
||||||
|
runParser,
|
||||||
|
liftOpt,
|
||||||
|
mapParser,
|
||||||
|
optionNames
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.Lens.Common
|
import Data.Lens.Common
|
||||||
@ -7,16 +18,6 @@ import Data.Maybe
|
|||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Options.Applicative.Types
|
import Options.Applicative.Types
|
||||||
|
|
||||||
optNameStr :: OptName -> String
|
|
||||||
optNameStr (OptLong name) = name
|
|
||||||
optNameStr (OptShort n) = [n]
|
|
||||||
|
|
||||||
isLong, isShort :: OptName -> Bool
|
|
||||||
isLong (OptLong _ ) = True
|
|
||||||
isLong _ = False
|
|
||||||
isShort (OptShort _ ) = True
|
|
||||||
isShort _ = False
|
|
||||||
|
|
||||||
optionNames :: OptReader a -> [OptName]
|
optionNames :: OptReader a -> [OptName]
|
||||||
optionNames (OptReader names _) = names
|
optionNames (OptReader names _) = names
|
||||||
optionNames (FlagReader names _) = names
|
optionNames (FlagReader names _) = names
|
||||||
|
@ -1,5 +1,30 @@
|
|||||||
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
|
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
|
||||||
module Options.Applicative.Builder where
|
module Options.Applicative.Builder (
|
||||||
|
-- * Readers
|
||||||
|
auto,
|
||||||
|
str,
|
||||||
|
disabled,
|
||||||
|
-- * Combinators
|
||||||
|
short,
|
||||||
|
long,
|
||||||
|
help,
|
||||||
|
value,
|
||||||
|
metavar,
|
||||||
|
reader,
|
||||||
|
hide,
|
||||||
|
multi,
|
||||||
|
command,
|
||||||
|
idm,
|
||||||
|
(&),
|
||||||
|
-- * Parsers
|
||||||
|
subparser,
|
||||||
|
argument,
|
||||||
|
arguments,
|
||||||
|
flag,
|
||||||
|
nullOption,
|
||||||
|
strOption,
|
||||||
|
option
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Category
|
import Control.Category
|
||||||
@ -21,10 +46,6 @@ data FlagFields a = FlagFields
|
|||||||
data CommandFields a = CommandFields
|
data CommandFields a = CommandFields
|
||||||
{ _cmdCommands :: [(String, ParserInfo a)] }
|
{ _cmdCommands :: [(String, ParserInfo a)] }
|
||||||
|
|
||||||
data ArgFields a = ArgFields
|
|
||||||
|
|
||||||
data CmdFields a = CmdFields
|
|
||||||
|
|
||||||
$( makeLenses [ ''OptionFields
|
$( makeLenses [ ''OptionFields
|
||||||
, ''FlagFields
|
, ''FlagFields
|
||||||
, ''CommandFields ] )
|
, ''CommandFields ] )
|
||||||
|
@ -1,4 +1,8 @@
|
|||||||
module Options.Applicative.Extra where
|
module Options.Applicative.Extra (
|
||||||
|
helper,
|
||||||
|
execParser,
|
||||||
|
usage
|
||||||
|
) where
|
||||||
|
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative.Types
|
||||||
@ -18,16 +22,16 @@ helper = nullOption
|
|||||||
& hide )
|
& hide )
|
||||||
|
|
||||||
execParser :: ParserInfo a -> IO a
|
execParser :: ParserInfo a -> IO a
|
||||||
execParser info = do
|
execParser pinfo = do
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
let p = infoParser info
|
let p = infoParser pinfo
|
||||||
case runParser p args of
|
case runParser p args of
|
||||||
Just (a, []) -> return a
|
Just (a, []) -> return a
|
||||||
_ -> do
|
_ -> do
|
||||||
prog <- getProgName
|
prog <- getProgName
|
||||||
let info' = info
|
let pinfo' = pinfo
|
||||||
{ infoHeader = vcat [infoHeader info, usage p prog] }
|
{ infoHeader = vcat [infoHeader pinfo, usage p prog] }
|
||||||
hPutStr stderr $ parserHelpText info'
|
hPutStr stderr $ parserHelpText pinfo'
|
||||||
exitWith (ExitFailure 1)
|
exitWith (ExitFailure 1)
|
||||||
|
|
||||||
usage :: Parser a -> String -> String
|
usage :: Parser a -> String -> String
|
||||||
|
@ -1,5 +1,11 @@
|
|||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
module Options.Applicative.Help where
|
module Options.Applicative.Help (
|
||||||
|
optDesc,
|
||||||
|
cmdDesc,
|
||||||
|
shortDesc,
|
||||||
|
fullDesc,
|
||||||
|
parserHelpText,
|
||||||
|
) where
|
||||||
|
|
||||||
import Data.Lens.Common
|
import Data.Lens.Common
|
||||||
import Data.List
|
import Data.List
|
||||||
|
@ -1,5 +1,20 @@
|
|||||||
{-# LANGUAGE GADTs, DeriveFunctor, TemplateHaskell #-}
|
{-# LANGUAGE GADTs, DeriveFunctor, TemplateHaskell #-}
|
||||||
module Options.Applicative.Types where
|
module Options.Applicative.Types (
|
||||||
|
ParserInfo(..),
|
||||||
|
info,
|
||||||
|
Option(..),
|
||||||
|
OptName(..),
|
||||||
|
OptReader(..),
|
||||||
|
Parser(..),
|
||||||
|
P(..),
|
||||||
|
|
||||||
|
optMain,
|
||||||
|
optDefault,
|
||||||
|
optShow,
|
||||||
|
optHelp,
|
||||||
|
optMetaVar,
|
||||||
|
optCont
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
@ -1,4 +1,9 @@
|
|||||||
module Options.Applicative.Utils where
|
module Options.Applicative.Utils (
|
||||||
|
(<+>),
|
||||||
|
vcat,
|
||||||
|
tabulate,
|
||||||
|
pad
|
||||||
|
) where
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative
|
||||||
import Options.Applicative.Builder
|
import Options.Applicative.Builder
|
||||||
import Options.Applicative.Extra
|
import Options.Applicative.Extra
|
||||||
|
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative
|
||||||
import Options.Applicative.Builder
|
import Options.Applicative.Builder
|
||||||
import Options.Applicative.Extra
|
import Options.Applicative.Extra
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user