1module Options.Applicative.Builder (
2  -- * Parser builders
3  --
4  -- | This module contains utility functions and combinators to create parsers
5  -- for individual options.
6  --
7  -- Each parser builder takes an option modifier. A modifier can be created by
8  -- composing the basic modifiers provided by this module using the 'Monoid'
9  -- operations 'mempty' and 'mappend', or their aliases 'idm' and '<>'.
10  --
11  -- For example:
12  --
13  -- > out = strOption
14  -- >     ( long "output"
15  -- >    <> short 'o'
16  -- >    <> metavar "FILENAME" )
17  --
18  -- creates a parser for an option called \"output\".
19  subparser,
20  strArgument,
21  argument,
22  flag,
23  flag',
24  switch,
25  abortOption,
26  infoOption,
27  strOption,
28  option,
29  nullOption,
30
31  -- * Modifiers
32  short,
33  long,
34  help,
35  helpDoc,
36  value,
37  showDefaultWith,
38  showDefault,
39  metavar,
40  noArgError,
41  ParseError(..),
42  hidden,
43  internal,
44  style,
45  command,
46  commandGroup,
47  completeWith,
48  action,
49  completer,
50  idm,
51  mappend,
52
53  -- * Readers
54  --
55  -- | A collection of basic 'Option' readers.
56  auto,
57  str,
58  maybeReader,
59  eitherReader,
60  disabled,
61  readerAbort,
62  readerError,
63
64  -- * Builder for 'ParserInfo'
65  InfoMod,
66  fullDesc,
67  briefDesc,
68  header,
69  headerDoc,
70  footer,
71  footerDoc,
72  progDesc,
73  progDescDoc,
74  failureCode,
75  noIntersperse,
76  forwardOptions,
77  info,
78
79  -- * Builder for 'ParserPrefs'
80  PrefsMod,
81  multiSuffix,
82  disambiguate,
83  showHelpOnError,
84  showHelpOnEmpty,
85  noBacktrack,
86  subparserInline,
87  columns,
88  helpLongEquals,
89  prefs,
90  defaultPrefs,
91
92  -- * Types
93  Mod,
94  ReadM,
95  OptionFields,
96  FlagFields,
97  ArgumentFields,
98  CommandFields,
99
100  HasName,
101  HasCompleter,
102  HasValue,
103  HasMetavar
104  ) where
105
106import Control.Applicative
107import Data.Semigroup hiding (option)
108import Data.String (fromString, IsString)
109
110import Options.Applicative.Builder.Completer
111import Options.Applicative.Builder.Internal
112import Options.Applicative.Common
113import Options.Applicative.Types
114import Options.Applicative.Help.Pretty
115import Options.Applicative.Help.Chunk
116
117-- Readers --
118
119-- | 'Option' reader based on the 'Read' type class.
120auto :: Read a => ReadM a
121auto = eitherReader $ \arg -> case reads arg of
122  [(r, "")] -> return r
123  _         -> Left $ "cannot parse value `" ++ arg ++ "'"
124
125-- | String 'Option' reader.
126--
127--   Polymorphic over the `IsString` type class since 0.14.
128str :: IsString s => ReadM s
129str = fromString <$> readerAsk
130
131-- | Convert a function producing an 'Either' into a reader.
132--
133-- As an example, one can create a ReadM from an attoparsec Parser
134-- easily with
135--
136-- > import qualified Data.Attoparsec.Text as A
137-- > import qualified Data.Text as T
138-- > attoparsecReader :: A.Parser a -> ReadM a
139-- > attoparsecReader p = eitherReader (A.parseOnly p . T.pack)
140eitherReader :: (String -> Either String a) -> ReadM a
141eitherReader f = readerAsk >>= either readerError return . f
142
143-- | Convert a function producing a 'Maybe' into a reader.
144maybeReader :: (String -> Maybe a) -> ReadM a
145maybeReader f = do
146  arg  <- readerAsk
147  maybe (readerError $ "cannot parse value `" ++ arg ++ "'") return . f $ arg
148
149-- | Null 'Option' reader. All arguments will fail validation.
150disabled :: ReadM a
151disabled = readerError "disabled option"
152
153-- modifiers --
154
155-- | Specify a short name for an option.
156short :: HasName f => Char -> Mod f a
157short = fieldMod . name . OptShort
158
159-- | Specify a long name for an option.
160long :: HasName f => String -> Mod f a
161long = fieldMod . name . OptLong
162
163-- | Specify a default value for an option.
164--
165-- /Note/: Because this modifier means the parser will never fail,
166-- do not use it with combinators such as 'some' or 'many', as
167-- these combinators continue until a failure occurs.
168-- Careless use will thus result in a hang.
169--
170-- To display the default value, combine with showDefault or
171-- showDefaultWith.
172value :: HasValue f => a -> Mod f a
173value x = Mod id (DefaultProp (Just x) Nothing) id
174
175-- | Specify a function to show the default value for an option.
176showDefaultWith :: (a -> String) -> Mod f a
177showDefaultWith s = Mod id (DefaultProp Nothing (Just s)) id
178
179-- | Show the default value for this option using its 'Show' instance.
180showDefault :: Show a => Mod f a
181showDefault = showDefaultWith show
182
183-- | Specify the help text for an option.
184help :: String -> Mod f a
185help s = optionMod $ \p -> p { propHelp = paragraph s }
186
187-- | Specify the help text for an option as a 'Text.PrettyPrint.ANSI.Leijen.Doc'
188-- value.
189helpDoc :: Maybe Doc -> Mod f a
190helpDoc doc = optionMod $ \p -> p { propHelp = Chunk doc }
191
192-- | Specify the error to display when no argument is provided to this option.
193noArgError :: ParseError -> Mod OptionFields a
194noArgError e = fieldMod $ \p -> p { optNoArgError = const e }
195
196-- | Specify a metavariable for the argument.
197--
198-- Metavariables have no effect on the actual parser, and only serve to specify
199-- the symbolic name for an argument to be displayed in the help text.
200metavar :: HasMetavar f => String -> Mod f a
201metavar var = optionMod $ \p -> p { propMetaVar = var }
202
203-- | Hide this option from the brief description.
204hidden :: Mod f a
205hidden = optionMod $ \p ->
206  p { propVisibility = min Hidden (propVisibility p) }
207
208-- | Apply a function to the option description in the usage text.
209--
210-- > import Options.Applicative.Help
211-- > flag' () (short 't' <> style bold)
212--
213-- /NOTE/: This builder is more flexible than its name and example
214-- allude. One of the motivating examples for its addition was to
215-- used `const` to completely replace the usage text of an option.
216style :: ( Doc -> Doc ) -> Mod f a
217style x = optionMod $ \p ->
218  p { propDescMod = Just x }
219
220-- | Add a command to a subparser option.
221--
222-- Suggested usage for multiple commands is to add them to a single subparser. e.g.
223--
224-- @
225-- sample :: Parser Sample
226-- sample = subparser
227--        ( command "hello"
228--          (info hello (progDesc "Print greeting"))
229--       <> command "goodbye"
230--          (info goodbye (progDesc "Say goodbye"))
231--        )
232-- @
233command :: String -> ParserInfo a -> Mod CommandFields a
234command cmd pinfo = fieldMod $ \p ->
235  p { cmdCommands = (cmd, pinfo) : cmdCommands p }
236
237-- | Add a description to a group of commands.
238--
239-- Advanced feature for separating logical groups of commands on the parse line.
240--
241-- If using the same `metavar` for each group of commands, it may yield a more
242-- attractive usage text combined with `hidden` for some groups.
243commandGroup :: String -> Mod CommandFields a
244commandGroup g = fieldMod $ \p ->
245  p { cmdGroup = Just g }
246
247-- | Add a list of possible completion values.
248completeWith :: HasCompleter f => [String] -> Mod f a
249completeWith = completer . listCompleter
250
251-- | Add a bash completion action. Common actions include @file@ and
252-- @directory@. See
253-- <http://www.gnu.org/software/bash/manual/html_node/Programmable-Completion-Builtins.html#Programmable-Completion-Builtins>
254-- for a complete list.
255action :: HasCompleter f => String -> Mod f a
256action = completer . bashCompleter
257
258-- | Add a completer to an argument.
259--
260-- A completer is a function String -> IO String which, given a partial
261-- argument, returns all possible completions for that argument.
262completer :: HasCompleter f => Completer -> Mod f a
263completer f = fieldMod $ modCompleter (`mappend` f)
264
265-- parsers --
266
267-- | Builder for a command parser. The 'command' modifier can be used to
268-- specify individual commands.
269subparser :: Mod CommandFields a -> Parser a
270subparser m = mkParser d g rdr
271  where
272    Mod _ d g = metavar "COMMAND" `mappend` m
273    (groupName, cmds, subs) = mkCommand m
274    rdr = CmdReader groupName cmds subs
275
276-- | Builder for an argument parser.
277argument :: ReadM a -> Mod ArgumentFields a -> Parser a
278argument p (Mod f d g) = mkParser d g (ArgReader rdr)
279  where
280    ArgumentFields compl = f (ArgumentFields mempty)
281    rdr = CReader compl p
282
283-- | Builder for a 'String' argument.
284strArgument :: IsString s => Mod ArgumentFields s -> Parser s
285strArgument = argument str
286
287-- | Builder for a flag parser.
288--
289-- A flag that switches from a \"default value\" to an \"active value\" when
290-- encountered. For a simple boolean value, use `switch` instead.
291--
292-- /Note/: Because this parser will never fail, it can not be used with
293-- combinators such as 'some' or 'many', as these combinators continue until
294-- a failure occurs. See @flag'@.
295flag :: a                         -- ^ default value
296     -> a                         -- ^ active value
297     -> Mod FlagFields a          -- ^ option modifier
298     -> Parser a
299flag defv actv m = flag' actv m <|> pure defv
300
301-- | Builder for a flag parser without a default value.
302--
303-- Same as 'flag', but with no default value. In particular, this flag will
304-- never parse successfully by itself.
305--
306-- It still makes sense to use it as part of a composite parser. For example
307--
308-- > length <$> many (flag' () (short 't'))
309--
310-- is a parser that counts the number of "-t" arguments on the command line,
311-- alternatively
312--
313-- > flag' True (long "on") <|> flag' False (long "off")
314--
315-- will require the user to enter '--on' or '--off' on the command line.
316flag' :: a                         -- ^ active value
317      -> Mod FlagFields a          -- ^ option modifier
318      -> Parser a
319flag' actv (Mod f d g) = mkParser d g rdr
320  where
321    rdr = let fields = f (FlagFields [] actv)
322          in FlagReader (flagNames fields)
323                        (flagActive fields)
324
325-- | Builder for a boolean flag.
326--
327-- /Note/: Because this parser will never fail, it can not be used with
328-- combinators such as 'some' or 'many', as these combinators continue until
329-- a failure occurs. See @flag'@.
330--
331-- > switch = flag False True
332switch :: Mod FlagFields Bool -> Parser Bool
333switch = flag False True
334
335-- | An option that always fails.
336--
337-- When this option is encountered, the option parser immediately aborts with
338-- the given parse error.  If you simply want to output a message, use
339-- 'infoOption' instead.
340abortOption :: ParseError -> Mod OptionFields (a -> a) -> Parser (a -> a)
341abortOption err m = option (readerAbort err) . (`mappend` m) $ mconcat
342  [ noArgError err
343  , value id
344  , metavar "" ]
345
346-- | An option that always fails and displays a message.
347infoOption :: String -> Mod OptionFields (a -> a) -> Parser (a -> a)
348infoOption = abortOption . InfoMsg
349
350-- | Builder for an option taking a 'String' argument.
351strOption :: IsString s => Mod OptionFields s -> Parser s
352strOption = option str
353
354-- | Same as 'option'.
355{-# DEPRECATED nullOption "Use 'option' instead" #-}
356nullOption :: ReadM a -> Mod OptionFields a -> Parser a
357nullOption = option
358
359-- | Builder for an option using the given reader.
360--
361-- This is a regular option, and should always have either a @long@ or
362-- @short@ name specified in the modifiers (or both).
363--
364-- > nameParser = option str ( long "name" <> short 'n' )
365--
366option :: ReadM a -> Mod OptionFields a -> Parser a
367option r m = mkParser d g rdr
368  where
369    Mod f d g = metavar "ARG" `mappend` m
370    fields = f (OptionFields [] mempty ExpectsArgError)
371    crdr = CReader (optCompleter fields) r
372    rdr = OptReader (optNames fields) crdr (optNoArgError fields)
373
374-- | Modifier for 'ParserInfo'.
375newtype InfoMod a = InfoMod
376  { applyInfoMod :: ParserInfo a -> ParserInfo a }
377
378instance Monoid (InfoMod a) where
379  mempty = InfoMod id
380  mappend = (<>)
381
382instance Semigroup (InfoMod a) where
383  m1 <> m2 = InfoMod $ applyInfoMod m2 . applyInfoMod m1
384
385-- | Show a full description in the help text of this parser.
386fullDesc :: InfoMod a
387fullDesc = InfoMod $ \i -> i { infoFullDesc = True }
388
389-- | Only show a brief description in the help text of this parser.
390briefDesc :: InfoMod a
391briefDesc = InfoMod $ \i -> i { infoFullDesc = False }
392
393-- | Specify a header for this parser.
394header :: String -> InfoMod a
395header s = InfoMod $ \i -> i { infoHeader = paragraph s }
396
397-- | Specify a header for this parser as a 'Text.PrettyPrint.ANSI.Leijen.Doc'
398-- value.
399headerDoc :: Maybe Doc -> InfoMod a
400headerDoc doc = InfoMod $ \i -> i { infoHeader = Chunk doc }
401
402-- | Specify a footer for this parser.
403footer :: String -> InfoMod a
404footer s = InfoMod $ \i -> i { infoFooter = paragraph s }
405
406-- | Specify a footer for this parser as a 'Text.PrettyPrint.ANSI.Leijen.Doc'
407-- value.
408footerDoc :: Maybe Doc -> InfoMod a
409footerDoc doc = InfoMod $ \i -> i { infoFooter = Chunk doc }
410
411-- | Specify a short program description.
412progDesc :: String -> InfoMod a
413progDesc s = InfoMod $ \i -> i { infoProgDesc = paragraph s }
414
415-- | Specify a short program description as a 'Text.PrettyPrint.ANSI.Leijen.Doc'
416-- value.
417progDescDoc :: Maybe Doc -> InfoMod a
418progDescDoc doc = InfoMod $ \i -> i { infoProgDesc = Chunk doc }
419
420-- | Specify an exit code if a parse error occurs.
421failureCode :: Int -> InfoMod a
422failureCode n = InfoMod $ \i -> i { infoFailureCode = n }
423
424-- | Disable parsing of regular options after arguments. After a positional
425--   argument is parsed, all remaining options and arguments will be treated
426--   as a positional arguments. Not recommended in general as users often
427--   expect to be able to freely intersperse regular options and flags within
428--   command line options.
429noIntersperse :: InfoMod a
430noIntersperse = InfoMod $ \p -> p { infoPolicy = NoIntersperse }
431
432-- | Intersperse matched options and arguments normally, but allow unmatched
433--   options to be treated as positional arguments.
434--   This is sometimes useful if one is wrapping a third party cli tool and
435--   needs to pass options through, while also providing a handful of their
436--   own options. Not recommended in general as typos by the user may not
437--   yield a parse error and cause confusion.
438forwardOptions :: InfoMod a
439forwardOptions = InfoMod $ \p -> p { infoPolicy = ForwardOptions }
440
441-- | Create a 'ParserInfo' given a 'Parser' and a modifier.
442info :: Parser a -> InfoMod a -> ParserInfo a
443info parser m = applyInfoMod m base
444  where
445    base = ParserInfo
446      { infoParser = parser
447      , infoFullDesc = True
448      , infoProgDesc = mempty
449      , infoHeader = mempty
450      , infoFooter = mempty
451      , infoFailureCode = 1
452      , infoPolicy = Intersperse }
453
454newtype PrefsMod = PrefsMod
455  { applyPrefsMod :: ParserPrefs -> ParserPrefs }
456
457instance Monoid PrefsMod where
458  mempty = PrefsMod id
459  mappend = (<>)
460
461instance Semigroup PrefsMod where
462  m1 <> m2 = PrefsMod $ applyPrefsMod m2 . applyPrefsMod m1
463
464-- | Include a suffix to attach to the metavar when multiple values
465--   can be entered.
466multiSuffix :: String -> PrefsMod
467multiSuffix s = PrefsMod $ \p -> p { prefMultiSuffix = s }
468
469-- | Turn on disambiguation.
470--
471--   See
472--   https://github.com/pcapriotti/optparse-applicative#disambiguation
473disambiguate :: PrefsMod
474disambiguate = PrefsMod $ \p -> p { prefDisambiguate = True }
475
476-- | Show full help text on any error.
477showHelpOnError :: PrefsMod
478showHelpOnError = PrefsMod $ \p -> p { prefShowHelpOnError = True }
479
480-- | Show the help text if the user enters only the program name or
481--   subcommand.
482--
483--   This will suppress a "Missing:" error and show the full usage
484--   instead if a user just types the name of the program.
485showHelpOnEmpty :: PrefsMod
486showHelpOnEmpty = PrefsMod $ \p -> p { prefShowHelpOnEmpty = True }
487
488-- | Turn off backtracking after subcommand is parsed.
489noBacktrack :: PrefsMod
490noBacktrack = PrefsMod $ \p -> p { prefBacktrack = NoBacktrack }
491
492-- | Allow full mixing of subcommand and parent arguments by inlining
493-- selected subparsers into the parent parser.
494--
495-- /NOTE:/ When this option is used, preferences for the subparser which
496-- effect the parser behaviour (such as noIntersperse) are ignored.
497subparserInline :: PrefsMod
498subparserInline = PrefsMod $ \p -> p { prefBacktrack = SubparserInline }
499
500-- | Set the maximum width of the generated help text.
501columns :: Int -> PrefsMod
502columns cols = PrefsMod $ \p -> p { prefColumns = cols }
503
504-- | Show equals sign, rather than space, in usage and help text for options with
505-- long names.
506helpLongEquals :: PrefsMod
507helpLongEquals = PrefsMod $ \p -> p { prefHelpLongEquals = True }
508
509-- | Create a `ParserPrefs` given a modifier
510prefs :: PrefsMod -> ParserPrefs
511prefs m = applyPrefsMod m base
512  where
513    base = ParserPrefs
514      { prefMultiSuffix = ""
515      , prefDisambiguate = False
516      , prefShowHelpOnError = False
517      , prefShowHelpOnEmpty = False
518      , prefBacktrack = Backtrack
519      , prefColumns = 80
520      , prefHelpLongEquals = False }
521
522-- Convenience shortcuts
523
524-- | Trivial option modifier.
525idm :: Monoid m => m
526idm = mempty
527
528-- | Default preferences.
529defaultPrefs :: ParserPrefs
530defaultPrefs = prefs idm
531