是否可以使用带有多个参数的optparse-applicative选项?

时间:2016-12-16 13:01:18

标签: haskell optparse-applicative

我发现我精心设计的解析器无法解析我抛出的任何字符串:

roi :: Parser (Maybe ROI)
roi = optional $ option (ROI <$> auto <*> auto <*> auto <*> auto)
               $ long "roi" <> metavar "ROI" <> help "Only process selected region of interest"

其中ROI = ROI Int Int Int Int

如果这很重要,它会嵌套在更高的解析器中

options :: Parser Opts
options = Opts <$> input <*> output <*> roi <*> startT <*> endT  

其中Opts是适当的ADT。

现在我假设roi解析器将解析--roi 1 2 3 4之类的表达式,但它会失败并显示Invalid argument '128'并给我用法消息。

--roi 1改为解析但返回Just (ROI 1 1 1 1)

有没有办法让这项工作?

2 个答案:

答案 0 :(得分:6)

我不认为选项应该使用多个参数。至少我不确定你是如何实现这一点的。我建议您放弃这个想法,并使用--roi 1,2,3,4之类的语法将ROI选项放入单个参数中。

你只需要为此实现一个自定义阅读器,这里有一个如何做到这一点的例子:

module Main where

import Options.Applicative

data ROI = ROI Int Int Int Int
  deriving Show

-- didn't remember what this function was called, don't use this
splitOn :: Eq a => a -> [a] -> [[a]]
splitOn sep (x:xs) | sep==x     = [] : splitOn sep xs
                   | otherwise = let (xs':xss) = splitOn sep xs in (x:xs'):xss
splitOn _ [] = [[]]

roiReader :: ReadM ROI
roiReader = do
  o <- str
  -- no error checking, don't actually do this
  let [a,b,c,d] = map read $ splitOn ',' o
  return $ ROI a b c d

roiParser :: Parser ROI
roiParser = option roiReader (long "roi")

main :: IO ()
main = execParser opts >>= print where
  opts = info (helper <*> roiParser) fullDesc

答案 1 :(得分:5)

option的类型是:

option :: ReadM a -> Mod OptionFields a -> Parser a
反过来,

ReadM是“读取字符串除外的新类型”,由选项读者使用。由于option正在使用ReaderT,因此当您使用Applicative ReadM实例时,就像在此处使用{...}}一样......

ROI <$> auto <*> auto <*> auto <*> auto

...相同的,整个输入字符串被提供给四个auto解析器中的每一个,因为这是读者/函数应用实例的工作方式。

如果希望将由空格分隔的值解析为单个ROI,则需要编写自定义解析器。这是围绕eitherReader建立的一个不是特别整洁的尝试。请注意,这将要求值在引号(--roi "1 2 3 4")内,以便将它们作为单个字符串引入。 Cubic的答案提出了一种替代方法,它使用逗号分隔值(--roi 1,2,3,4)。

import Text.Read (readEither)

-- etc.

roi :: Parser (Maybe ROI)
roi = optional
    $ option (eitherReader $ \inp -> case traverse readEither (words inp) of
        Right [x, y, z, w] -> Right (ROI x y z w)
        Right _ -> Left "ROI requires exactly 4 values"
        Left _ -> Left "ROI requires integer values")
    $ long "roi" <> metavar "ROI" <> help "Only process selected region of interest"

成功和失败模式:

GHCi> execParserPure defaultPrefs (info roi mempty) ["--roi","1 2 3 4"]
Success (Just (ROI 1 2 3 4))
GHCi> execParserPure defaultPrefs (info roi mempty) ["--roi","1 2 3"]
Failure (ParserFailure (option --roi: ROI requires exactly 4 values

Usage: <program> [--roi ROI],ExitFailure 1,80))
GHCi> execParserPure defaultPrefs (info roi mempty) ["--roi","1 2 foo 4"]
Failure (ParserFailure (option --roi: ROI requires integer values

Usage: <program> [--roi ROI],ExitFailure 1,80))