module Multiarg.Limeline where
import Multiarg.Types
import Multiarg.Maddash
import Prelude hiding (Word)
data PosArg a = PosArg a
deriving (Eq, Ord, Show)
instance Functor PosArg where
fmap f (PosArg a) = PosArg (f a)
interspersed
:: [(ShortName, ArgSpec a)]
-> [(LongName, ArgSpec a)]
-> (String -> a)
-> [Word]
-> ([Either [Output a] (PosArg a)], Maybe OptName)
interspersed shorts longs fTok = go
where
go toks = (map Left outs ++ outsRest, err)
where
(outs, ei) = processWords shorts longs toks
(outsRest, err) = case ei of
Left (opt, _) -> ([], Just opt)
Right [] -> ([], Nothing)
Right ((Word x):xs)
| x == "--" ->
( map (\(Word t) -> Right . PosArg . fTok $ t) xs
, Nothing )
| otherwise -> ( (Right . PosArg . fTok $ x) : rest
, mayErrRest )
where
(rest, mayErrRest) = go xs