Skip to content

Commit

Permalink
Add Parser groups, similar to Command groups
Browse files Browse the repository at this point in the history
Adds the ability to group options together, similar to command
groups. The parser groups semantics are:

1. Consecutive duplicate groups are merged.
2. Non-consecutive duplicate groups are __not__ merged.
3. Nested groups are concatenated together e.g. if "Group B" is parsed
   within "Group A", then B's options will render under
   "Group A.Group B".

1 and 2 is the same behavior as Command groups.
  • Loading branch information
tbidne authored and HuwCampbell committed Jul 22, 2024
1 parent 9da7065 commit 2403294
Show file tree
Hide file tree
Showing 22 changed files with 1,122 additions and 14 deletions.
6 changes: 6 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
## Version 0.19.0.0

- Add `parserOptionGroup` for grouping Options together, similar to command
groups. Requires the breaking change of adding the `propGroup :: OptGroup`
field to `OptProperties`.

## Version 0.18.1.0 (29 May 2023)

- Change pretty printer layout algorithm used.
Expand Down
42 changes: 42 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -748,6 +748,48 @@ main = customExecParser p opts
p = prefs showHelpOnEmpty
```

#### Option groups

The `parserOptionGroup` function can be used to group options together under
a common heading. For example, if we have:

```haskell
Args
<$> parseMain
<*> parserOptionGroup "Group A" parseA
<*> parserOptionGroup "Group B" parseB
<*> parseOther
```

Then the `--help` page `Available options` will look like:

```
Available options:
<main options>
Group A:
<A options>
Group B:
<B options>
Available options:
<other options>
```

Caveats:

- Parser groups are like command groups in that groups are listed in creation
order, and (non-consecutive) duplicate groups are allowed.

- Nested groups are concatenated:

```haskell
parserOptionGroup "Group A" (parserOptionGroup "Group Z" parseA)
```

Will group `parseA` under `GroupA.Group Z`.

### Command groups

One experimental feature which may be useful for programs with many
Expand Down
11 changes: 11 additions & 0 deletions optparse-applicative.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,11 @@ extra-source-files: CHANGELOG.md
tests/formatting-long-subcommand.err.txt
tests/nested.err.txt
tests/optional.err.txt
tests/parser_group_all_grouped.err.txt
tests/parser_group_basic.err.txt
tests/parser_group_command_groups.err.txt
tests/parser_group_duplicates.err.txt
tests/parser_group_nested.err.txt
tests/nested_optional.err.txt
tests/subparsers.err.txt

Expand Down Expand Up @@ -131,6 +136,12 @@ test-suite tests
, Examples.Formatting
, Examples.Hello
, Examples.LongSub
, Examples.ParserGroup.AllGrouped
, Examples.ParserGroup.Basic
, Examples.ParserGroup.CommandGroups
, Examples.ParserGroup.DuplicateCommandGroups
, Examples.ParserGroup.Duplicates
, Examples.ParserGroup.Nested

build-depends: base
, optparse-applicative
Expand Down
1 change: 1 addition & 0 deletions src/Options/Applicative.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,7 @@ module Options.Applicative (
completer,
idm,
mappend,
parserOptionGroup,

OptionFields,
FlagFields,
Expand Down
61 changes: 61 additions & 0 deletions src/Options/Applicative/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ module Options.Applicative.Builder (
completer,
idm,
mappend,
parserOptionGroup,

-- * Readers
--
Expand Down Expand Up @@ -118,6 +119,7 @@ import Options.Applicative.Common
import Options.Applicative.Types
import Options.Applicative.Help.Pretty
import Options.Applicative.Help.Chunk
import Options.Applicative.Internal (mapParserOptions)

-- Readers --

Expand Down Expand Up @@ -379,6 +381,65 @@ option r m = mkParser d g rdr
crdr = CReader (optCompleter fields) r
rdr = OptReader (optNames fields) crdr (optNoArgError fields)

-- | Prepends a group to 'OptProperties'. Nested groups are concatenated
-- together e.g.
--
-- @
-- optPropertiesGroup "Group Outer" (optPropertiesGroup "Group Inner" o)
-- @
--
-- will render as "Group Outer.Group Inner".
optPropertiesGroup :: String -> OptProperties -> OptProperties
optPropertiesGroup g o = o { propGroup = OptGroup (g : gs) }
where
OptGroup gs = propGroup o

-- | Prepends a group per 'optPropertiesGroup'.
optionGroup :: String -> Option a -> Option a
optionGroup grp o = o { optProps = props' }
where
props' = optPropertiesGroup grp (optProps o)

-- | This function can be used to group options together under a common
-- heading. For example, if we have:
--
-- > Args
-- > <$> parseMain
-- > <*> parserOptionGroup "Group A" parseA
-- > <*> parserOptionGroup "Group B" parseB
-- > <*> parseOther
--
-- Then the help page will look like:
--
-- > Available options:
-- > <main options>
-- >
-- > Group A:
-- > <A options>
-- >
-- > Group B:
-- > <B options>
-- >
-- > Available options:
-- > <other options>
--
-- Caveats:
--
-- - Parser groups are like command groups in that groups are listed in
-- creation order, and (non-consecutive) duplicate groups are allowed.
--
-- - Nested groups are concatenated:
--
-- @
-- parserOptionGroup "Group A" (parserOptionGroup "Group Z" parseA)
-- @
--
-- Will group @parseA@ under @"GroupA.Group Z"@.
--
-- @since 0.19.0.0
parserOptionGroup :: String -> Parser a -> Parser a
parserOptionGroup g = mapParserOptions (optionGroup g)

-- | Modifier for 'ParserInfo'.
newtype InfoMod a = InfoMod
{ applyInfoMod :: ParserInfo a -> ParserInfo a }
Expand Down
1 change: 1 addition & 0 deletions src/Options/Applicative/Builder/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,7 @@ baseProps = OptProperties
, propShowDefault = Nothing
, propDescMod = Nothing
, propShowGlobal = True
, propGroup = OptGroup []
}

mkCommand :: Mod CommandFields a -> (Maybe String, [(String, ParserInfo a)])
Expand Down
51 changes: 39 additions & 12 deletions src/Options/Applicative/Help/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,9 @@ module Options.Applicative.Help.Core (
import Control.Applicative
import Control.Monad (guard)
import Data.Function (on)
import Data.List (sort, intersperse, groupBy)
import Data.List (sort, intercalate, intersperse, groupBy)
import Data.Foldable (any, foldl')
import Data.Maybe (catMaybes, fromMaybe)
import Data.Maybe (fromMaybe)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (mempty)
#endif
Expand All @@ -34,6 +34,7 @@ import Data.Semigroup (Semigroup (..))
import Prelude hiding (any)

import Options.Applicative.Common
import Options.Applicative.Internal (groupFst)
import Options.Applicative.Types
import Options.Applicative.Help.Pretty
import Options.Applicative.Help.Chunk
Expand All @@ -50,12 +51,13 @@ safelast :: [a] -> Maybe a
safelast = foldl' (const Just) Nothing

-- | Generate description for a single option.
optDesc :: ParserPrefs -> OptDescStyle -> ArgumentReachability -> Option a -> (Chunk Doc, Parenthetic)
optDesc :: ParserPrefs -> OptDescStyle -> ArgumentReachability -> Option a -> (OptGroup, Chunk Doc, Parenthetic)
optDesc pprefs style _reachability opt =
let names =
sort . optionNames . optMain $ opt
meta =
stringChunk $ optMetaVar opt
grp = propGroup $ optProps opt
descs =
map (pretty . showOption) names
descriptions =
Expand Down Expand Up @@ -86,7 +88,7 @@ optDesc pprefs style _reachability opt =
desc
modified =
maybe id fmap (optDescMod opt) rendered
in (modified, wrapping)
in (grp, modified, wrapping)

-- | Generate descriptions for commands.
cmdDesc :: ParserPrefs -> Parser a -> [(Maybe String, Chunk Doc)]
Expand Down Expand Up @@ -118,7 +120,7 @@ briefDesc' showOptional pprefs =
wrapOver NoDefault MaybeRequired
. foldTree pprefs style
. mfilterOptional
. treeMapParser (optDesc pprefs style)
. treeMapParser (\a -> (\(_, x, y) -> (x, y)) . optDesc pprefs style a)
where
mfilterOptional
| showOptional =
Expand Down Expand Up @@ -193,14 +195,41 @@ globalDesc = optionsDesc True

-- | Common generator for full descriptions and globals
optionsDesc :: Bool -> ParserPrefs -> Parser a -> Chunk Doc
optionsDesc global pprefs = tabulate (prefTabulateFill pprefs) . catMaybes . mapParser doc
optionsDesc global pprefs p = vsepChunks
. fmap formatTitle
. fmap tabulateGroup
. groupByTitle
$ mapParser doc p
where
groupByTitle :: [Maybe (OptGroup, (Doc, Doc))] -> [[(OptGroup, (Doc, Doc))]]
groupByTitle = groupFst

tabulateGroup :: [(OptGroup, (Doc, Doc))] -> (OptGroup, Chunk Doc)
tabulateGroup l@((title,_):_) = (title, tabulate (prefTabulateFill pprefs) (snd <$> l))
tabulateGroup [] = mempty

-- Note that we treat Global/Available options identically, when it comes
-- to titles.
formatTitle :: (OptGroup, Chunk Doc) -> Chunk Doc
formatTitle (OptGroup groups, opts) =
case groups of
[] -> (pretty defTitle .$.) <$> opts
gs@(_:_) -> (renderGroupStr gs .$.) <$> opts
where
defTitle =
if global
then "Global options:"
else "Available options:"

renderGroupStr = (<> pretty ":") . pretty . intercalate "."

doc :: ArgumentReachability -> Option a -> Maybe (OptGroup, (Doc, Doc))
doc info opt = do
guard . not . isEmpty $ n
guard . not . isEmpty $ h
return (extractChunk n, align . extractChunk $ h <</>> hdef)
return (grp, (extractChunk n, align . extractChunk $ h <<+>> hdef))
where
n = fst $ optDesc pprefs style info opt
(grp, n, _) = optDesc pprefs style info opt
h = optHelp opt
hdef = Chunk . fmap show_def . optShowDefault $ opt
show_def s = parens (pretty "default:" <+> pretty s)
Expand Down Expand Up @@ -238,7 +267,7 @@ footerHelp chunk = mempty { helpFooter = chunk }
parserHelp :: ParserPrefs -> Parser a -> ParserHelp
parserHelp pprefs p =
bodyHelp . vsepChunks $
with_title "Available options:" (fullDesc pprefs p)
(fullDesc pprefs p)
: (group_title <$> cs)
where
def = "Available commands:"
Expand All @@ -255,9 +284,7 @@ parserHelp pprefs p =

parserGlobals :: ParserPrefs -> Parser a -> ParserHelp
parserGlobals pprefs p =
globalsHelp $
(.$.) <$> stringChunk "Global options:"
<*> globalDesc pprefs p
globalsHelp $ globalDesc pprefs p



Expand Down
27 changes: 27 additions & 0 deletions src/Options/Applicative/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE RankNTypes #-}

module Options.Applicative.Internal
( P
, MonadP(..)
Expand All @@ -24,6 +26,9 @@ module Options.Applicative.Internal
, cut
, (<!>)
, disamb

, mapParserOptions
, groupFst
) where

import Control.Applicative
Expand All @@ -35,6 +40,9 @@ import Control.Monad.Trans.Except
import Control.Monad.Trans.Reader
(mapReaderT, runReader, runReaderT, Reader, ReaderT, ask)
import Control.Monad.Trans.State (StateT, get, put, modify, evalStateT, runStateT)
import Data.Function (on)
import Data.List (groupBy)
import Data.Maybe (catMaybes)

import Options.Applicative.Types

Expand Down Expand Up @@ -266,3 +274,22 @@ hoistList :: Alternative m => [a] -> m a
hoistList = foldr cons empty
where
cons x xs = pure x <|> xs

-- | Strips 'Nothing', then groups on the first element of the tuple.
--
-- @since 0.19.0.0
groupFst :: (Eq a) => [Maybe (a, b)] -> [[(a, b)]]
groupFst = groupBy ((==) `on` fst) . catMaybes

-- | Maps an Option modifying function over the Parser.
--
-- @since 0.19.0.0
mapParserOptions :: (forall x. Option x -> Option x) -> Parser a -> Parser a
mapParserOptions f = go
where
go :: forall y. Parser y -> Parser y
go (NilP x) = NilP x
go (OptP o) = OptP (f o)
go (MultP p1 p2) = MultP (go p1) (go p2)
go (AltP p1 p2) = AltP (go p1) (go p2)
go (BindP p1 p2) = BindP (go p1) (\x -> go (p2 x))
Loading

0 comments on commit 2403294

Please sign in to comment.