summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2016-04-25 18:50:54 -0400
committerjoe <joe@jerkface.net>2016-04-25 18:50:54 -0400
commitd69f91416952f43ba42c7fe0839091ef6b0ed4bf (patch)
tree942499a511b254487f6e235f913314fde5ca7097
parentbf1f1e3ec434272fe452f9b3016050b17b456eb2 (diff)
Fixed fancy commandline parsing.
-rw-r--r--lib/CommandLine.hs75
1 files changed, 68 insertions, 7 deletions
diff --git a/lib/CommandLine.hs b/lib/CommandLine.hs
index 88584ce..62f0315 100644
--- a/lib/CommandLine.hs
+++ b/lib/CommandLine.hs
@@ -9,7 +9,9 @@ module CommandLine
9 ( Args 9 ( Args
10 , UsageError(..) 10 , UsageError(..)
11 , usageErrorMessage 11 , usageErrorMessage
12 , parseInvocation 12 , ArgsStyle(..)
13 , vanilla
14 , fancy
13 , runArgs 15 , runArgs
14 , arg 16 , arg
15 , param 17 , param
@@ -235,7 +237,7 @@ param :: Int -> Args String
235param n = Args (Prim (\_ us -> us!!n) (singleton $ exactly (n+1))) [] 237param n = Args (Prim (\_ us -> us!!n) (singleton $ exactly (n+1))) []
236 238
237arg :: String -> Args String 239arg :: String -> Args String
238arg optname = Args (Prim (\opts _ -> head $ concat $ take 1 opts) 240arg optname = Args (Prim (\opts _ -> concat $ take 1 $ concat $ take 1 opts)
239 (singleton $ exactly 0)) 241 (singleton $ exactly 0))
240 [optname] 242 [optname]
241 243
@@ -247,7 +249,7 @@ label :: String -> Args a -> Args a
247label _ = id 249label _ = id
248 250
249data ArgsStyle = ArgsStyle 251data ArgsStyle = ArgsStyle
250 { parseInvocation :: String -> [String] -> ([(String,[String])], [String]) 252 { parseInvocation :: [String] -> ([(String,[String])], [String])
251 } 253 }
252 254
253-- | Phase 1. This function accepts a list of command line arguments in its 255-- | Phase 1. This function accepts a list of command line arguments in its
@@ -262,8 +264,8 @@ data ArgsStyle = ArgsStyle
262-- unnamed argument values. 264-- unnamed argument values.
263-- 265--
264-- The results of this function are intended to be used as input to 'runArgs'. 266-- The results of this function are intended to be used as input to 'runArgs'.
265vanilla :: ArgsStyle 267vanilla :: String -> ArgsStyle
266vanilla = ArgsStyle { parseInvocation = parse } 268vanilla flags = ArgsStyle { parseInvocation = parse flags }
267 where 269 where
268 parse flags cli = (opts, concat nons ++ nondashed ++ drop 1 trailing) 270 parse flags cli = (opts, concat nons ++ nondashed ++ drop 1 trailing)
269 where 271 where
@@ -275,6 +277,65 @@ vanilla = ArgsStyle { parseInvocation = parse }
275 splitParams (('-':[x]):xs) | x `elem` flags = (['-':[x]],xs) 277 splitParams (('-':[x]):xs) | x `elem` flags = (['-':[x]],xs)
276 splitParams xs = splitAt 2 xs 278 splitParams xs = splitAt 2 xs
277 279
280-- |
281-- Arguments:
282--
283-- * option-count pairs - List of option names paired with number of expected values to follow them.
284--
285-- * polyvariadic options - List of option names that can take any number of arguments.
286--
287-- * default polyvariadic - Implicit polyvariadic option if no other option is specified.
288--
289fancy sargspsec polyVariadicArgs defaultPoly = ArgsStyle
290 { parseInvocation = parse sargspsec polyVariadicArgs defaultPoly }
291 where
292 parse sargspec polyVariadicArgs defaultPoly args_raw = (Map.toList $ fst margs, snd margs)
293 where
294 (args,trail1) = break (=="--") args_raw
295 trail = drop 1 trail1
296 commonArgSpec = []
297 -- [ ("--homedir",1) , ("--passphrase-fd",1) , ("--help",0) ]
298 sargspec' = commonArgSpec ++ sargspec
299 (sargs,margs) = (sargs, tackTail mapped )
300 where (sargs,vargs) = partitionStaticArguments sargspec' args
301 argspec = map fst sargspec' ++ polyVariadicArgs
302 args' = if null defaultPoly || map (take 1) (take 1 vargs) == ["-"]
303 then vargs
304 else defaultPoly:vargs
305 -- grouped args
306 gargs = (sargs ++)
307 . (if null defaultPoly then id else toLast (++trail))
308 . groupBy (\_ s-> take 1 s /= "-")
309 $ args'
310 append (m,as) (k:xs)
311 | k `elem` argspec = (Map.alter (appendArgs k xs) k m,as)
312 | null defaultPoly && "-" == take 1 k
313 = (Map.alter (appendArgs k xs) k m,as)
314 | otherwise = (m,as ++ (k:xs))
315 appendArgs k xs opt = Just . maybe xs (++xs) $ opt
316 mapped = foldl' append (Map.empty,[]) gargs
317 tackTail | null defaultPoly = second (++trail)
318 | otherwise = id
319
320 -- partitionStaticArguments :: Ord a => [(a, Int)] -> [a] -> ([[a]], [a])
321 partitionStaticArguments specs args = psa args
322 where
323 smap = Map.fromList specs
324 psa [] = ([],[])
325 psa (a:as) =
326 case Map.lookup a smap of
327 Nothing | (k,'=':v) <- break (=='=') a
328 , Just 1 <- Map.lookup k smap
329 -> first ([k,v]:) $ psa as
330 Nothing -> second (a:) $ psa as
331 Just n -> first ((a:take n as):) $ psa (drop n as)
332
333 -- | Returns the given list with its last element modified.
334 toLast :: (x -> x) -> [x] -> [x]
335 toLast f [] = []
336 toLast f [x] = [f x]
337 toLast f (x:xs) = x : toLast f xs
338
278-- | Information about how the user failed to satisfy a specified usage. 339-- | Information about how the user failed to satisfy a specified usage.
279data UsageError 340data UsageError
280 = TooManyParameters Int 341 = TooManyParameters Int
@@ -409,9 +470,9 @@ runArgs (os,us) c
409 dups = mapMaybe notSingle $ groupBy ((==) `on` fst) (os' :: [(String,[String])]) 470 dups = mapMaybe notSingle $ groupBy ((==) `on` fst) (os' :: [(String,[String])])
410 where notSingle [x] = Nothing 471 where notSingle [x] = Nothing
411 notSingle ((k,v):xs) = Just (k,v : map snd xs) 472 notSingle ((k,v):xs) = Just (k,v : map snd xs)
412 getbit = let r = Map.fromList $ zip (accepts c) [0..] in trace ("getbit = "++show r) r 473 getbit = Map.fromList $ zip (accepts c) [0..]
413 goods :: [(Int,[String])] 474 goods :: [(Int,[String])]
414 (bads,goods) = let r = partitionEithers $ map f os' in trace ("(bads,goods)="++show r) r 475 (bads,goods) = partitionEithers $ map f os'
415 where f (k,v) = case Map.lookup k getbit of 476 where f (k,v) = case Map.lookup k getbit of
416 Just b -> Right (b,v) 477 Just b -> Right (b,v)
417 Nothing -> Left (k,v) 478 Nothing -> Left (k,v)