[Haskell-cafe] optparse-applicative in stack LTS <= 9.3

Viktor Dukhovni ietf-dane at dukhovni.org
Wed Sep 6 19:26:52 UTC 2017


FYI, the version of optparse-applicative (0.13.2.0) in Stack LTS-9.3
and earlier does not appear to handle the "noIntersperse" info modifier
correctly.  Instead of stopping parsing flags after the first non-option
argument, it instead simply never parses any options.  This is fixed in
0.14.0.0, which is in "Stackage Nightly".

Perhaps someone else will run into the same issue.  And it would of course
be nice to see 0.14.0.0 appear in an upcoming LTS version (say 9.4).

-- 
	Viktor.

Demo program, this fails to even process "--help" with the outdated
optparse-applicative, which just reports all arguments as positional:

module Main (main) where

import           Options.Applicative
import           Data.Monoid ((<>))

data Opts = Opts
  { bl :: Bool
  , fl :: Bool
  , st :: Maybe String
  , pos :: String
  , args :: [String] }
  deriving (Show)

main :: IO ()
main = do
 let parse = Opts <$> switch ( long "bool" <> short 'b' )
                  <*> switch ( long "flag" <> short 'f' )
                  <*> optional ( strOption ( long "string" <> short 's' ) )
                  <*> strArgument ( metavar "FILE" )
                  <*> many ( strArgument ( metavar "ARGS..." ) )
     i = info (helper <*> parse)
         $ fullDesc
         <> noIntersperse
         <> header "Option parser"
         <> progDesc "- test POSIX-style options"
 execParser i >>= print



-- 
	Viktor.



More information about the Haskell-Cafe mailing list