Howto create a nested/conditional option with optparse-applicative? - haskell

Is possible to create a haskell expression, using the methods in optparse-applicative, that parses program options like this?
program [-a [-b]] ...
-a and -b are optionals flags (implemented using switch), with the constraint that the -b option only is valid if -a is typed before.
Thanks

This is possible, with slight tweaks, two different ways:
You can make a parser that only allows -b if you've got -a, but you can't insist then that the -a comes first, since optparse-applicative's <*> combinator doesn't specify an order.
You can insist that the -b option follows the a option, but you do this by implementing a as a command, so you lose the - in front of it.
Applicative is definitely strong enough for this, since there's no need to inspect the values returned by the parsers to determine whether -b is allowed, so >>= is not necessary; If -a succeeds with any output, -b is allowed.
Examples
I'll use a data type to represent which arguments are present, but in reality these would be more meaningful.
import Options.Applicative
data A = A (Maybe B) deriving Show
data B = B deriving Show
So the options to our program maybe contain an A, which might have a B, and always have a string.
boption :: Parser (Maybe B)
boption = flag Nothing (Just B) (short 'b')
Way 1: standard combinators - -b can only come with -a (any order)
I'll use flag' () (short 'a') which just insists that -a is there, but then use *> instead of <*> to ignore the return value () and just return whatever the boption parser returns, giving options -a [-b]. I'll then tag that with A :: Maybe B -> A and finally I'll make the whole thing optional, so you have options [-a [-b]]
aoption :: Parser (Maybe A)
aoption = optional $ A <$> (flag' () (short 'a' ) *> boption)
main = execParser (info (helper <*> aoption)
(fullDesc <> progDesc "-b is only valid with -a"))
>>= print
Notice that since <*> allows any order, we can put -a after -b (which isn't quite what you asked for, but works OK and makes sense for some applications).
ghci> :main -a
Just (A Nothing)
ghci> :main -a -b
Just (A (Just B))
ghci> :main -b -a
Just (A (Just B))
ghci> :main -b
Usage: <interactive> [-a] [-b]
-b is only valid with -a
*** Exception: ExitFailure 1
Way 2: command subparser - -b can only follow a
You can use command to make a subparser which is only valid when the command string is present. You can use it to handle arguments like cabal does, so that cabal install and cabal update have completely different options. Since command takes a ParserInfo argument, any parser you can give to execParser can be used, so you can actually nest commands arbitrarily deeply. Sadly, commands can't start with -, so it'll be program [a [-b]] ... instead of program [-a [-b]] ....
acommand :: Parser A
acommand = subparser $ command "a" (info (A <$> (helper <*> boption))
(progDesc "you can '-b' if you like with 'a'"))
main = execParser (info (helper <*> optional acommand) fullDesc) >>= print
Which runs like this:
ghci> :main
Nothing
ghci> :main a
Just (A Nothing)
ghci> :main a -b
Just (A (Just B))
ghci> :main -b a
Usage: <interactive> [COMMAND]
*** Exception: ExitFailure 1
So you have to precede -b with a.

I'm afraid you can't. This is precisely the scenario that Applicative alone can't handle while Monad can: changing the structure of later actions based on earlier results. In an applicative computation, the "shape" always needs to be known beforehand; this has some advantages (like speeding up so array combinations, or giving out a nice readable help screen for command-line options), but here it limits you to parsing "flat" options.
The interface of optparse-applicative also has Alternative though, which does allow dependent parsing, albeit in a different way as shown by AndrewC.

Related

How do I create, and distinguish, global options using 'optparse-applicative'?

In my Haskell executable, created using optparse-applicative, I would like to have a global option for --version alongside the global --help option that is available from all subcommands. However the example provided (see below) for adding a --version option to to a CLI with subcommands results in a --version option that is inconsistently available
$ cli create --version
Invalid option `--version'
Usage: cli create NAME
Create a thing
$ cli delete --version
0.0
and never shows up in help for subcommands
$ cli create -h
Usage: cli create NAME
Create a thing
Available options:
NAME Name of the thing to create
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Available options:
-h,--help Show this help text
The behavior I would like is for --version to be available globally and to all subcommands:
$ cli create -h
Usage: cli create NAME
Create a thing
Available options:
NAME Name of the thing to create
--version Show version
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Available options:
--version Show version
-h,--help Show this help text
$ cli create --version
0.0
$ cli delete --version
0.0
It's not clear from the documentation how to achieve this.
In fact, I'd ideally like to be able to clearly group options in the help output:
$ cli create -h
Usage: cli create NAME
Create a thing
Arguments:
NAME Name of the thing to create
Global options:
--version Show version
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Global options:
--version Show version
-h,--help Show this help text
Is there a way to achieve this using optparse-applicative?
{-#LANGUAGE ScopedTypeVariables#-}
import Data.Semigroup ((<>))
import Options.Applicative
data Opts = Opts
{ optGlobalFlag :: !Bool
, optCommand :: !Command
}
data Command
= Create String
| Delete
main :: IO ()
main = do
(opts :: Opts) <- execParser optsParser
case optCommand opts of
Create name -> putStrLn ("Created the thing named " ++ name)
Delete -> putStrLn "Deleted the thing!"
putStrLn ("global flag: " ++ show (optGlobalFlag opts))
where
optsParser :: ParserInfo Opts
optsParser =
info
(helper <*> versionOption <*> programOptions)
(fullDesc <> progDesc "optparse subcommands example" <>
header
"optparse-sub-example - a small example program for optparse-applicative with subcommands")
versionOption :: Parser (a -> a)
versionOption = infoOption "0.0" (long "version" <> help "Show version")
programOptions :: Parser Opts
programOptions =
Opts <$> switch (long "global-flag" <> help "Set a global flag") <*>
hsubparser (createCommand <> deleteCommand)
createCommand :: Mod CommandFields Command
createCommand =
command
"create"
(info createOptions (progDesc "Create a thing"))
createOptions :: Parser Command
createOptions =
Create <$>
strArgument (metavar "NAME" <> help "Name of the thing to create")
deleteCommand :: Mod CommandFields Command
deleteCommand =
command
"delete"
(info (pure Delete) (progDesc "Delete the thing"))
As far as I know, this (in particular, the categorized help text) isn't really easy to do with optparse-applicative, since it isn't quite the pattern that they were planning for with global arguments. If you are okay with using program --global-options command --local-options (which is a fairly standard pattern) instead of program command --global-and-local-options, then you can use the approach shown in the linked example:
$ ./optparse-sub-example
optparse-sub-example - a small example program for optparse-applicative with
subcommands
Usage: optparse [--version] [--global-flag] COMMAND
optparse subcommands example
Available options:
-h,--help Show this help text
--version Show version
--global-flag Set a global flag
Available commands:
create Create a thing
delete Delete the thing
$ ./optparse-sub-example --version create
0.0
$ ./optparse-sub-example --version delete
0.0
$ ./optparse-sub-example --global-flag create HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag delete
Deleted the thing!
global flag: True
(Note: I would advise going with this approach, since "global options before the command" is fairly standard).
If you also want the global options to be available in every subcommand, you will have a few issues.
As far as I know, there is no way to affect the help text output in order to group them separately inside the individual command help texts.
You will need some custom subparser-like function that adds your global options & merges them with any global options before the command.
For #2, one way to restructure the example to support this might be something along these lines:
To start with, standard boilerplate and imports:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ApplicativeDo #-}
import Data.Monoid
import Data.Semigroup ((<>))
import Options.Applicative
import Options.Applicative.Types
Opts are explicitly split into optGlobals and optCommand, making it easy to deal with all of the global options at once if more are available:
data Opts = Opts
{ optGlobals :: !GlobalOpts
, optCommand :: !Command
}
data GlobalOpts = GlobalOpts { optGlobalFlag :: Bool }
GlobalOpts should be a Semigroup and a Monoid, since we need to merge options seen at various different points (before the command, after the command, etc.). It should also be possible, with suitable alterations to mysubparser below, to require global options to be given only after commands and omit this requirement.
instance Semigroup GlobalOpts where
-- Code for merging option parser results from the multiple parsers run
-- at various different places. Note that this may be run with the default
-- values returned by one parser (from a location with no options present)
-- and the true option values from another, so it may be important
-- to distinguish between "the default value" and "no option" (since "no
-- option" shouldn't override another value provided earlier, while
-- "user-supplied value that happens to match the default" probably should).
--
-- In this case this doesn't matter, since the flag being provided anywhere
-- should be enough for it to be considered true.
(GlobalOpts f1) <> (GlobalOpts f2) = GlobalOpts (f1 || f2)
instance Monoid GlobalOpts where
-- Default values for the various options. These should probably match the
-- defaults used in the option declarations.
mempty = GlobalOpts False
As before, a Command type to represent the different possible commands:
data Command
= Create String
| Delete
The real magic: mysubparser wraps hsubparser to add global options and deal with merging them. It takes the parser for global options as an argument:
mysubparser :: forall a b. Monoid a
=> Parser a
-> Mod CommandFields b
-> Parser (a, b)
mysubparser globals cmds = do
To start with, it runs the global parser (to catch any globals given before a command):
g1 <- globals
It then uses hsubparser to get a command parser, and modifies it to also parse global options:
(g2, r) <- addGlobals $ hsubparser cmds
Finally, it merges the two global option sets, and returns the parsed global options and the command parser result:
pure (g1 <> g2, r)
where
The addGlobals helper function:
addGlobals :: forall c. Parser c -> Parser (a, c)
If NilP was given, we just use mempty to get the default option set:
addGlobals (NilP x) = NilP $ (mempty,) <$> x
The important case: if we have an OptP around an Option that uses a CommandReader, the globals parser is added to every command parser:
addGlobals (OptP (Option (CmdReader n cs g) ps)) =
OptP (Option (CmdReader n cs $ fmap go . g) ps)
where go pi = pi { infoParser = (,) <$> globals <*> infoParser pi }
In all other cases, either just use the default option set, or merge option sets from recursive Parsers as appropriate:
addGlobals (OptP o) = OptP ((mempty,) <$> o)
addGlobals (AltP p1 p2) = AltP (addGlobals p1) (addGlobals p2)
addGlobals (MultP p1 p2) =
MultP ((\(g2, f) -> \(g1, x) -> (g1 <> g2, f x)) <$> addGlobals p1)
(addGlobals p2)
addGlobals (BindP p k) = BindP (addGlobals p) $ \(g1, x) ->
BindP (addGlobals $ k x) $ \(g2, x') ->
pure (g1 <> g2, x')
Modifications to the main function are fairly minimal, and mostly related to using the new GlobalOpts. Once a parser for GlobalOpts is available, passing it to mysubparser is quite easy:
main :: IO ()
main = do
(opts :: Opts) <- execParser optsParser
case optCommand opts of
Create name -> putStrLn ("Created the thing named " ++ name)
Delete -> putStrLn "Deleted the thing!"
putStrLn ("global flag: " ++ show (optGlobalFlag (optGlobals opts)))
where
optsParser :: ParserInfo Opts
optsParser =
info
(helper <*> programOptions)
(fullDesc <> progDesc "optparse subcommands example" <>
header
"optparse-sub-example - a small example program for optparse-applicative with subcommands")
versionOption :: Parser (a -> a)
versionOption = infoOption "0.0" (long "version" <> help "Show version")
globalOpts :: Parser GlobalOpts
globalOpts = versionOption <*>
(GlobalOpts <$> switch (long "global-flag" <> help "Set a global flag"))
programOptions :: Parser Opts
programOptions =
uncurry Opts <$> mysubparser globalOpts (createCommand <> deleteCommand)
createCommand :: Mod CommandFields Command
createCommand =
command
"create"
(info createOptions (progDesc "Create a thing"))
createOptions :: Parser Command
createOptions =
Create <$>
strArgument (metavar "NAME" <> help "Name of the thing to create")
deleteCommand :: Mod CommandFields Command
deleteCommand =
command
"delete"
(info (pure Delete) (progDesc "Delete the thing"))
Notice that mysubparser should be a quite generic/reusable component.
This exhibits behavior closer to what you wanted:
$ ./optparse-sub-example create --global-flag HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag create HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag delete
Deleted the thing!
global flag: True
$ ./optparse-sub-example delete --global-flag
Deleted the thing!
global flag: True
$ ./optparse-sub-example delete
Deleted the thing!
global flag: False
$ ./optparse-sub-example delete --version
0.0
$ ./optparse-sub-example create --version
0.0

Strange behaviour of `ReadP` with regards to `fmap head`

Consider the following repl session:
λ import Text.ParserCombinators.ReadP
λ x $$ y = readP_to_S x y
-- This auxiliary function makes things tidier.
λ many get $$ "abc"
[("","abc"),("a","bc"),("ab","c"),("abc","")]
-- This is reasonable.
λ fmap head (many get) $$ "abc"
[(*** Exception: Prelude.head: empty list
-- Wut?
λ fmap last (many get) $$ "abc"
[(*** Exception: Prelude.last: empty list
-- This works neither.
λ fmap id (many get) $$ "abc"
[("","abc"),("a","bc"),("ab","c"),("abc","")]
-- The list is there until I try to chop its head!
My questions:
What is happening here?
How can I extract a single (preferably longest) parse result?
P.S. My goal is to construct a parser combinator that greedily returns the repetitive application of a given parser. (get in this instance, but in actuality I have a more involved logic.) Chopping the list of intermediate results is one approach I thought would do, but I am fine with any, except that it is preferable not to convert to ReadS and back.

Turtle: how to read a list of files?

Assume we have a file my_file.txt with contents:
foo
bar
and another file my_other_file.txt containing:
baz
I would like to read the contents of these two files using turtle so that I get a Shell of lines which will produce:
foo
bar
baz
In Haskell's turtle library one can read a list of files by using input, for instance:
view $ input "my_file.txt"
We have that
input :: FilePath -> Shell Line
And Shell has no Monoid instances (which I think makes sense since we cannot associate IO operations), so the only operator I can think of using is (<|>):
view $ foldl (<|>) empty $ map input ["my_file.txt", "my_other_file.txt"]
While this produces the desired effect, I wonder whether there is a library in the turtle eco-system that takes care of this, or whether there is a traverse like operation that can be use on Alternative's.
EDIT: the effect above could be also achieved by using asum:
asum $ input <$> ["my_file.txt", "my_other_file.txt"]
Line has a Monoid instance. If we have a list of Lines, we can mconcat them into a single one:
do
exampleA <- input "my_file.txt"
exampleB <- input "my_other_file.txt"
return $ mconcat [exampleA, exampleB]
Since Shell has an Applicative instance, we can use traverse to use input over a list of files:
traverse input ["my_file.txt","my_other_file.txt"]
We end up with a Shell [Line]. Since Shell is a Functor, we can fmap mconcat (or fold if you don't use a list):
mconcat <$> traverse input ["my_file.txt","my_other_file.txt"]

Haskell: use of unsafePerformIO for global constant bindings

There are lots of discussions of using unsafePerformIO carefully for global mutable variables, and some language additions to support it (e.g. Data.Global). I have a related but distinct question: using it for global constant bindings. Here’s a usage I consider entirely OK: command-line parsing.
module Main where
--------------------------------------------------------------------------------
import Data.Bool (bool)
import Data.Monoid ((<>))
import Options.Applicative (short, help, execParser, info, helper, fullDesc,
progDesc, long, switch)
import System.IO.Unsafe (unsafePerformIO)
--------------------------------------------------------------------------------
data CommandLine = CommandLine
Bool --quiet
Bool --verbose
Bool --force
commandLineParser = CommandLine
<$> switch
( long "quiet"
<> short 'q'
<> help "Show only error messages.")
<*> switch
( long "verbose"
<> short 'v'
<> help "Show lots of detail.")
<*> switch
( long "force"
<> short 'f'
<> help "Do stuff anyway.")
{- Parse the command line, and bind related values globally for
convenience. This use of unsafePerformIO is OK since the action has no
side effects and it's idempotent. -}
CommandLine cQuiet cVerbose cForce
= unsafePerformIO . execParser $ info (helper <*> commandLineParser)
( fullDesc
<> progDesc "example program"
)
-- Print a message:
say = say' $ not cQuiet -- unless --quiet
verbose = say' cVerbose -- if --verbose
say' = bool (const $ return ()) putStrLn
--------------------------------------------------------------------------------
main :: IO ()
main = do
verbose "a verbose message"
say "a regular message"
It is very valuable to be able to refer cQuiet, cVerbose, etc. globally rather than have to pass them around as arguments wherever they’re needed. After all, this is exactly what global identifiers are for: these have a single value that never changes during any run of the program — it just happens that the value is initialized from the outside world rather than declared in the program text.
It makes sense in principal to do the same thing with other sorts of constant data fetched from the outside, e.g. settings from a configuration file — but then an extra point arises: the action which fetches those is not idempotent, unlike reading the command line (I’m slightly abusing the term “idempotent” here, but trust that I’m understood). This just adds the constraint that the action must be performed only once. My question is: what’s the best way to do that with code of this form:
data Config = Foo String | Bar (Maybe String) | Baz Int
readConfig :: IO Config
readConfig = do …
Config foo bar baz = unsafePerformIO readConfig
The doc suggests to me that this is sufficient and none of the precautions mentioned there are needed, but I’m not sure. I’ve seen proposals for adding a top-level syntax inspired by do-notation specifically for such situations:
Config foo bar baz <- readConfig
… which seems like a very good idea; I’d rather be sure the action will be performed at most once than rely on various compiler settings and hope no compiler behavior comes along that breaks existing code.
I feel the fact that these are in fact constants, together with the ugliness involved in passing such things around explicitly despite the fact that they never change, argue strongly for there being a safe and supported way to do this. I’m open to hearing contrary opinions if someone thinks I’m missing an important point here, though.
Updates
The say and verbose uses in the example are not the best, because it’s not values in the IO monad that are the real annoyance — these could easily read the parameters from a global IORef. The problem is the use of such parameters pervasively in pure code, which have to all be rewritten to either take the parameters explicitly (even though these do not change and thus should not need to be function parameters), or be converted to IO which is even worse. I’ll improve the example when I have time.
Another way to think about this: the class of behaviors I’m talking about could be obtained in the following clunky way: run a program that fetches some data via I/O; take the results and substitute them into the template text of the main program as the values of some global bindings; then compile and run the resulting main program. You would then safely have the advantage of referring to those constants easily throughout the program. It seems that it should not be so hard to implement this pattern directly. I phrased the question mentioning unsafePerformIO, but really I’m interested in understanding this kind of behavior, and what the best way to obtain it would be. unsafePerformIO is one way, but it has drawbacks.
known limitations:
With unsafePerformIO, when the data-fetching action happens is not fixed. This may be a feature, so that e.g. an error related to a missing configuration parameter occurs if and only if that parameter is ever actually used. If you need different behavior, you’ll have to force the values with seq as needed.
I don't know if I'd consider top-level command line parsing to always be OK! Specifically, observe what happens with this alternate main when the user provides bad input.
main = do
putStrLn "Arbitrary program initialization"
verbose "a verbose message"
say "a regular message"
putStrLn "Clean shutdown"
> ./commands -x
Arbitrary program initialization
Invalid option `-x'
Usage: ...
Now in this case you can force one (or all!) of the pure values so that the parser is known to have run by a well-defined point in time.
main = do
() <- return $ cQuiet `seq` cVerbose `seq` cForce `seq` ()
-- ...
> ./commands -x
Invalid option `-x'
...
But what happens if you have something like—
forkIO (withArgs newArgs action)
The only sensible thing to do is {-# NOINLINE cQuiet #-} and friends, so some of those precautions in System.IO.Unsafe do apply to you. But this is an interesting case to patch over, note that you have given up the ability to run sub-computations with alternate values. An e.g. ReaderT solution using local doesn't have that drawback.
This seems an even larger drawback to me in the case of reading config files, as long running applications usually are reconfigurable without requiring a stop/start cycle. A top-level pure value precludes reconfiguration.
But maybe this is even more clear if you consider the intersection of both your config files and your command line arguments. In many utilities arguments on the command line override values provided in a config file, an impossible behavior given what you have now.
For toys, sure, go hog wild. For anything else, at least make your top-level value an IORef or MVar. There are some ways to still make the non-unsafePerformIO solutions nicer though. Consider—
data Config = Config { say :: String -> IO ()
, verbose :: String -> IO ()
}
mkSay :: Bool -> String -> IO ()
mkSay quiet s | quiet = return ()
| otherwise = putStrLn s
-- In some action...
let config = Config (mkSay quietFlag) (mkVerbose verboseFlag)
compute :: Config -> IO Value
compute config = do
-- ...
verbose config "Debugging info"
-- ...
This also respects the spirit of Haskell function signatures, in that it's now clear (without even needing to consider the open world of IO) that your functions' behavior actually does depend on program configuration.
-XImplicitParams is useful in this situation.
{-# LANGUAGE ImplicitParams #-}
data CommandLine = CommandLine
Bool --quiet
Bool --verbose
Bool --force
say' :: Bool -> String -> IO ()
say' = bool (const $ return ()) putStrLn
say, verbose :: (?cmdLine :: CommandLine) => String -> IO ()
say = case ?cmdLine of CommandLine cQuiet _ _ -> say' $ not cQuiet
verbose = case ?cmdLine of CommandLine _ cVerbose _ -> say' cVerbose
Anything that is implicitly typed and uses say or verbose will have the ?cmdLine :: CommandLine implicit parameter added to its type.
:type (\s -> say (show s))
(\s -> say (show s))
:: (Show a, ?cmdLine::CommandLine) => a -> IO ()
Two cases from Hackage that come to mind:
The package cmdargs makes use of unsafePerformIO - treating command line arguments as constant.
In the package oeis, the
"pure" function getSequenceByID uses unsafePerformIO to return content from a web page on http://oeis.org. It notes in its documentation:
Note that the result is not in the IO monad, even though the implementation requires looking up information via the Internet. There are no side effects to speak of, and from a practical point of view the function is referentially transparent (OEIS A-numbers could change in theory, but it's extremely unlikely).

optparse-applicative option with multiple values

I'm using optparse-applicative and I'd like to be able to parse command line arguments such as:
$ ./program -a file1 file2 -b filea fileb
i.e., two switches, both of which can take multiple arguments.
So I have a data type for my options which looks like this:
data MyOptions = MyOptions {
aFiles :: [String]
, bFiles :: [String] }
And then a Parser like this:
config :: Parser MyOptions
config = MyOptions
<$> option (str >>= parseStringList)
( short 'a' <> long "aFiles" )
<*> option (str >>= parseStringList)
( short 'b' <> long "bFiles" )
parseStringList :: Monad m => String -> m [String]
parseStringList = return . words
This approach fails in that it will give the expected result when just one argument is supplied for each switch, but if you supply a second argument you get "Invalid argument" for that second argument.
I wondered if I could kludge it by pretending that I wanted four options: a boolean switch (i.e. -a); a list of strings; another boolean switch (i.e. -b); and another list of strings. So I changed my data type:
data MyOptions = MyOptions {
isA :: Bool
, aFiles :: [String]
, isB :: Bool
, bFiles :: [String] }
And then modified the parser like this:
config :: Parser MyOptions
config = MyOptions
<$> switch
( short 'a' <> long "aFiles" )
<*> many (argument str (metavar "FILE"))
<*> switch
( short 'b' <> long "bFiles" )
<*> many (argument str (metavar "FILE"))
This time using the many and argument combinators instead of an explicit parser for a string list.
But now the first many (argument str (metavar "FILE")) consumes all of the arguments, including those following the -b switch.
So how can I write this arguments parser?
Aside from commands, optparse-applicative follows the getopts convention: a single argument on the command line corresponds to a single option argument. It's even a little bit more strict, since getopts will allow multiple options with the same switch:
./program-with-getopts -i input1 -i input2 -i input3
So there's no "magic" that can help you immediately to use your program like
./program-with-magic -a 1 2 3 -b foo bar crux
since Options.Applicative.Parser wasn't written with this in mind; it also contradicts the POSIX conventions, where options take either one argument or none.
However, you can tackle this problem from two sides: either use -a several times, as you would in getopts, or tell the user to use quotes:
./program-as-above -a "1 2 3" -b "foo bar crux"
# works already with your program!
To enable the multiple use of an option you have to use many (if they're optional) or some (if they aren't). You can even combine both variants:
multiString desc = concat <$> some single
where single = option (str >>= parseStringList) desc
config :: Parser MyOptions
config = MyOptions
<$> multiString (short 'a' <> long "aFiles" <> help "Use quotes/multiple")
<*> multiString (short 'b' <> long "bFiles" <> help "Use quotes/multiple")
which enables you to use
./program-with-posix-style -a 1 -a "2 3" -b foo -b "foo bar"
But your proposed style isn't supported by any parsing library I know, since the position of free arguments would be ambiguous. If you really want to use -a 1 2 3 -b foo bar crux, you have to parse the arguments yourself.

Resources