Skip to content
This repository has been archived by the owner on Apr 26, 2021. It is now read-only.

Commit

Permalink
Do not parse values w/ commas into lists
Browse files Browse the repository at this point in the history
Ensure comma separated values provided on the command line or through
the environment are *NOT* parsed into arrays. This has been identified
as flaw in design an is subject to removal from neodoc. This change
excludes default value declarations ([default: a,b,c]) since it's in the
developers control and comma-parsing can be skipped by quoting
([default: 'a,b,c']). This changeset further brings in a fix for the
Value module's read function.

Refer #16
  • Loading branch information
felixSchl committed Apr 26, 2016
1 parent dfbf4ec commit 5db64ac
Show file tree
Hide file tree
Showing 9 changed files with 92 additions and 44 deletions.
3 changes: 2 additions & 1 deletion package.json
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@
"bower": "^1.7.7",
"mocha": "^2.4.5",
"pulp": "^8.0.0",
"purescript": "^0.8.0"
"purescript": "^0.8.0",
"string-argv": "0.0.2"
}
}
6 changes: 6 additions & 0 deletions src/Data/String/Argv.js
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
/* global exports */
"use strict";

// module Data.String.Argv

exports.parse = require('string-argv');
5 changes: 5 additions & 0 deletions src/Data/String/Argv.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Data.String.Argv (parse) where

import Prelude

foreign import parse :: String -> Array String
2 changes: 1 addition & 1 deletion src/Language/Docopt/Parser/Desc.purs
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ isDefaultTag (Default _) = true
isDefaultTag _ = false

getDefaultValue :: Content -> Maybe Value
getDefaultValue (Default v) = either (const Nothing) Just (Value.parse v)
getDefaultValue (Default v) = either (const Nothing) Just (Value.parse v true)
getDefaultValue _ = Nothing

isEnvTag :: Content -> Boolean
Expand Down
12 changes: 6 additions & 6 deletions src/Language/Docopt/ParserGen/Parser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,7 @@ command n = token go P.<?> "command " ++ show n
positional :: String -> Parser D.Value
positional n = token go P.<?> "positional argument " ++ show n
where
go (Lit v) = Just (Value.read v)
go (Lit v) = Just (Value.read v false)
go _ = Nothing

dash :: Parser D.Value
Expand Down Expand Up @@ -192,9 +192,9 @@ longOption n a = P.ParserT $ \(P.PState { input: toks, position: pos }) ->
go (LOpt n' v) atok | (not isFlag) && (n' == n)
= case v of
Just s ->
return $ OptParse (Value.read s) Nothing false
return $ OptParse (Value.read s false) Nothing false
_ -> return case atok of
Just (Lit s) -> OptParse (Value.read s) Nothing true
Just (Lit s) -> OptParse (Value.read s false) Nothing true
_ -> OptParse (D.BoolValue true) Nothing false

-- case 2:
Expand All @@ -209,7 +209,7 @@ longOption n a = P.ParserT $ \(P.PState { input: toks, position: pos }) ->
-- provdided.
go (LOpt n' Nothing) _ | not isFlag
= case stripPrefix n n' of
Just s -> return $ OptParse (Value.read s) Nothing false
Just s -> return $ OptParse (Value.read s false) Nothing false
_ -> Left "Invalid substring"

go a b = Left $ "Invalid token" ++ show a ++ " (input: " ++ show b ++ ")"
Expand Down Expand Up @@ -249,7 +249,7 @@ shortOption f a = P.ParserT $ \(P.PState { input: toks, position: pos }) ->
= case v of
Just val -> return $ OptParse (D.StringValue val) Nothing false
_ -> return case atok of
Just (Lit s) -> OptParse (Value.read s) Nothing true
Just (Lit s) -> OptParse (Value.read s false) Nothing true
_ -> OptParse (D.BoolValue true)
Nothing
false
Expand All @@ -260,7 +260,7 @@ shortOption f a = P.ParserT $ \(P.PState { input: toks, position: pos }) ->
go (SOpt f' xs v) _ | (f' == f) && (not isFlag) && (A.length xs > 0)
= do
let a = fromCharArray xs ++ maybe "" id v
return $ OptParse (Value.read a)
return $ OptParse (Value.read a false)
Nothing
false

Expand Down
11 changes: 6 additions & 5 deletions src/Language/Docopt/Trans.purs
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,11 @@ reduce us env b vs =
applyValues :: Map Key D.Value -> List D.Argument -> Map Key D.Value
applyValues vm as = Map.fromFoldableWith resolveArg
$ catMaybes
$ as <#> \a -> Tuple (key a) <$> (getValue vm a <|> getFallback a)
$ as <#> \a -> Tuple (key a) <$> do
v <- (getValue vm a <|> getFallback a)
return $ if D.isRepeatable a
then D.ArrayValue $ valIntoArray v
else v

resolveArg :: D.Value -> D.Value -> D.Value
resolveArg v v' = D.ArrayValue $ valIntoArray v' ++ valIntoArray v
Expand Down Expand Up @@ -192,10 +196,7 @@ reduce us env b vs =

getValue :: Map Key D.Value -> D.Argument -> Maybe D.Value
getValue vm a = do
v <- Map.lookup (key a) vm
return $ if D.isRepeatable a
then D.ArrayValue $ valIntoArray v
else v
Map.lookup (key a) vm

getFallback :: D.Argument -> Maybe D.Value
getFallback a = getEnvValue a <|> getDefaultValue a
Expand Down
21 changes: 15 additions & 6 deletions src/Language/Docopt/Value.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,14 +10,15 @@ module Language.Docopt.Value (

import Prelude
import Unsafe.Coerce (unsafeCoerce)
import Control.Apply ((<*))
import Data.Generic (class Generic)
import Data.Either (Either(), either)
import Data.List (List(..), fromList, many, some)
import Control.Apply ((*>))
import Control.Alt ((<|>))
import Text.Parsing.Parser (ParseError, runParser, fail) as P
import Text.Parsing.Parser.Combinators (between, choice, try, sepBy1) as P
import Text.Parsing.Parser.String (noneOf, char, string) as P
import Text.Parsing.Parser.String (noneOf, char, string, eof) as P
import Data.Array as A
import Data.String (fromCharArray)
import Data.String as Str
Expand Down Expand Up @@ -78,8 +79,10 @@ prettyPrintValue (ArrayValue xs) = show $ prettyPrintValue <$> xs
prettyPrintValue (IntValue i) = show i
prettyPrintValue (FloatValue f) = show f

read :: String -> Value
read s = either (const $ StringValue s) id (parse s)
read :: String -- ^ the input
-> Boolean -- ^ allow splitting?
-> Value
read s split = either (const $ StringValue s) id (parse s split)

-- | Parse a string into a value
-- | Values can be command *AND* space separated:
Expand All @@ -89,8 +92,14 @@ read s = either (const $ StringValue s) id (parse s)
-- | a b, c -> [ a, b, c ]
-- | a, b c -> [ a, b, c ]
-- |
parse :: String -> Either P.ParseError Value
parse = flip P.runParser values
parse :: String -- ^ the input
-> Boolean -- ^ allow splitting?
-> Either P.ParseError Value
parse s split = P.runParser s do
v <- if split then values
else value
P.eof
return v

where
values = do
Expand All @@ -105,7 +114,7 @@ parse = flip P.runParser values

white = P.char ' ' <|> P.char '\n'

inner =do
inner = do
P.try value <|> do StringValue <$> do
fromCharArray <<< fromList <$> do
many $ P.try (P.noneOf [',', ' ', '\n'])
Expand Down
24 changes: 13 additions & 11 deletions test/Test/Spec/CompatSpec.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ import Control.Monad.Eff (Eff())
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Aff (Aff, later)
import Data.StrMap as StrMap
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..), fst, snd)
import Data.Either (Either(..), either)
import Control.Monad.Eff.Exception (EXCEPTION, error, throwException)
import Data.Foldable (intercalate, for_)
Expand All @@ -30,11 +30,12 @@ import Node.FS.Sync as FS
import Control.Apply ((*>), (<*))
import Data.Array as A
import Data.Int as Int
import Data.String.Argv as Argv

import Docopt as Docopt
import Language.Docopt (runDocopt)
import Language.Docopt.Value (Value(..), prettyPrintValue) as D
import Language.Docopt.Parser.Base (space, digit, alpha, upperAlpha)
import Language.Docopt.Parser.Base (space, digit, alpha, upperAlpha, getInput)

newtype Test = Test {
doc :: String
Expand Down Expand Up @@ -90,13 +91,9 @@ parseUniversalDocoptTests = do
} $ parseFlags <$> do
P.char '/'
fromCharArray <$> A.many alpha
P.skipSpaces
input <- flip P.sepBy (P.char ' ') do
many (P.char ' ')
fromCharArray <$> do
-- Note: Terminate on '{'. This is hacky and pragmatic,
-- but it doesn't have to be any more than that...
A.some $ P.noneOf [ ' ', '{', '\n', '"' ]
many (P.char ' ')
input <- Argv.parse <<< fromCharArray <<< fromList <$>
P.manyTill (P.noneOf ['\n']) (P.char '\n')
P.skipSpaces *> skipComments *> P.skipSpaces
output <- P.choice $ P.try <$>
[ Right <$> do
Expand All @@ -117,7 +114,7 @@ parseUniversalDocoptTests = do
P.skipSpaces *> skipComments *> P.skipSpaces
return $ Kase { out: output
, options: {
argv: return $ fromList input
argv: return input
, optionsFirst: flags.optionsFirst
, env: return env
, dontExit: true
Expand Down Expand Up @@ -183,7 +180,12 @@ genCompatSpec = do
describe (doc ++ "\n") do
for_ kases \(Kase { options, out }) -> do
let argv = fromJust options.argv
describe (intercalate " " argv) do
env = fromJust options.env
describe (intercalate " " $
(fromList $ StrMap.toList env <#> \t ->
fst t ++ "=\"" ++ snd t ++ "\"")
++ argv
) do
it ("\n" ++ prettyPrintOut out) do

-- XXX: Manually break the execution context in order to avoid to
Expand Down
52 changes: 38 additions & 14 deletions testcases.docopt
Original file line number Diff line number Diff line change
Expand Up @@ -1806,16 +1806,16 @@ $ prog -f 1 -f 2 -f 3 -f 4 -f 5 -f 6
"-f": [1, 2, 3, 4, 5, 6]}

$ prog -f 1,2,3,4,5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2,3,4,5,6"],
"-f": ["1,2,3,4,5,6"]}

$ prog -f 1,2,3 --foo 4,5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2,3", "4,5,6"],
"-f": ["1,2,3", "4,5,6"]}

$ prog -f 1,2 --foo 3,4 -f 5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2", "3,4", "5,6"],
"-f": ["1,2", "3,4", "5,6"]}

r"""
Usage:
Expand All @@ -1829,16 +1829,16 @@ $ prog -f 1 -f 2 -f 3 -f 4 -f 5 -f 6
"-f": [1, 2, 3, 4, 5, 6]}

$ prog -f 1,2,3,4,5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2,3,4,5,6"],
"-f": ["1,2,3,4,5,6"]}

$ prog -f 1,2,3 --foo 4,5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2,3", "4,5,6"],
"-f": ["1,2,3", "4,5,6"]}

$ prog -f 1,2 --foo 3,4 -f 5,6
{"--foo": [1, 2, 3, 4, 5, 6],
"-f": [1, 2, 3, 4, 5, 6]}
{"--foo": ["1,2", "3,4", "5,6"],
"-f": ["1,2", "3,4", "5,6"]}

#
# Issue #11
Expand Down Expand Up @@ -2245,7 +2245,31 @@ $ prog
"user-error"

$ INPUT="foo bar" prog
{"--input": "foo bar"}
{"--input": ["foo bar"]}

#
# Ensure comma separated values provided on the command line or through the
# environment are *NOT* parsed into arrays. This has been identified as flaw
# in design an is subject to removal from neodoc. This change excludes default
# value declarations ([default: a,b,c]) since it's in the developers control
# and comma-parsing can be skipped by quoting ([default: 'a,b,c'])
#
# Refer #16
#

r"""
Usage: foo --input=FILE...
Options: --input [env: INPUT]
"""

$ INPUT="foo,bar" prog
{"--input": "foo,bar"}
{"--input": ["foo,bar"]}

$ prog --input "foo bar"
{"--input": ["foo bar"]}

$ prog --input "foo,bar"
{"--input": ["foo,bar"]}

$ prog --input foo,bar
{"--input": ["foo,bar"]}

0 comments on commit 5db64ac

Please sign in to comment.