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