{-# OPTIONS -fglasgow-exts #-} -- | This module provides an advanced option parsing routine which can properly parse -- options depending on what types are infered for them as well as produce a pretty -- error message with usage info when an incorrect option is used. module GetOptions( -- * Functions -- ** Option Parsing getOptions, parseOptions, -- ** Option Augmentation (==>), (??), noHelp, -- * Types and Classes Option, ArgOption, HasDefault, HasHelp, NoHelp ) where import Control.Monad.Error import Control.Monad.Writer import List import Data.Monoid import Control.Monad import System import IO data ArgType = ArgYes | ArgNo | ArgMaybe -- | Type of arguments with a default value. data HasDefault a b = HasDefault a b deriving(Show) -- | Type of arguments with a user supplied help message. data HasHelp a = HasHelp String a deriving(Show) type SHasDefault b = HasDefault String b data Matching a = MatchOne a | MatchSome [Matching a] -- Why no FunctorM? matchingFmapM f (MatchOne x) = f x >>= return . MatchOne matchingFmapM f (MatchSome xs) = mapM (matchingFmapM f) xs >>= return . MatchSome matchFlatten x = f x [] where f (MatchOne x) y = x:y f (MatchSome xs) y = foldr ($) y (map f xs) infixl 2 ==> infixl 1 ?? -- | Specify a default value if an argument is not found. (==>) :: a -- ^ argument -> b -- ^ default value -> HasDefault a b a ==> b = HasDefault a b -- | Specify a help message. (??) :: a -- ^ argument -> String -- ^ help message -> HasHelp a a ?? b = HasHelp b a newtype NoHelp a = NoHelp a -- | Cause an option to not occur in the help message. noHelp :: a -> NoHelp a noHelp x = NoHelp x class Option a b where -- | should not be strict in a argGetInfo' :: a -> b -> Matching ([String],ArgType) -- | Process arguments, returning a proper value. argProcess' :: b -> Matching [(String,Maybe String)] -> Either String a argGetInfo :: a -> b -> ([String],ArgType) argProcess :: b -> [(String,Maybe String)] -> Either String a argGetInfo a b = case argGetInfo' a b of MatchOne x -> x _ -> error "argGetInfo: called with MatchSome" argProcess b ms = argProcess' b (MatchOne ms) argGetInfo' a b = MatchOne $ argGetInfo a b argProcess' a (MatchOne b) = argProcess a b argProcess' _ _ = error "argProcess': called with MatchSome" argHelp :: a -> b -> [([String],Maybe (Bool,String),String)] argHelp a b = map f $ matchFlatten (argGetInfo' a b) where f (ns,ArgYes) = (ns,Just (True,"ARG"),"") f (ns,ArgNo) = (ns,Nothing,"") f (ns,ArgMaybe) = (ns,Just (False,"ARG"),"") -- argShowHelp :: a -> b -> [] -- | Main Entry point. -- This retrieves the arguments passed to the program via 'getArgs' and runs parseOptions on it. -- In addition, it handles errors by printing a help message and exiting as well as creating a -- --help option to force a printing of the help table. -- -- The basic idea is that there is a matching between the data passed into -- getOptions and what is returned. In the examples below, I will include type information in comments for reference. -- This is not needed by the compiler however, as the proper types are infered. -- -- for instance -- -- > (args,verb) <- getOptions "v|verbose" -- verb :: Bool -- -- will cause verb == True if and only if --v or --verbose are on the command line. -- -- It is also possible for options to take arguments: -- -- > (args,(verb,output_name)) <- getOptions ("v|verbose", "o") -- verb :: Bool, output_name :: Maybe String -- -- will set output_name == Just \"foo\" iff -o foo is one of the arguments. (and set verb as above) -- -- In addition to strings, arguments may be many other basic types, such as Ints, Doubles, or even Either types. If the argument passed on the command line does not -- match the type needed, an appropriate error message will be generated. -- -- Note that multiple options are possible via tuples, which may also be nested. (useful for libraries) -- -- > (args,(verb,output_name)) <- getOptions ( -- > "v|verbose" -- > ,"o" ==> "out.txt" -- > ) -- verb :: Bool, output_name :: String -- -- Default options may also be specified with the '==>' operator. Notice the -- type of output_name is now String rather than Maybe String. -- -- Help messages may be specified with the '??' operator. -- -- For example -- -- > (as,(output_name,verb,count,xs)) <- getOptions ( -- > "o" ==> "out.txt" ?? "Specify output file" -- > ,"v|verbose" ?? "Enable verbose mode." -- > ,"count" ==> (1::Int) ?? "How many iterations" -- > ,"elem|e" ?? "A list of elements" -- > ) -- -- produces the following help table -- -- > -o out.txt Specify output file -- > -v, --verbose Enable verbose mode. -- > --count 1 How many iterations -- > --elem, -e ARG A list of elements -- > --help Display usage information -- -- If a list of items is returned, the option is allowed to occur multiple -- times and all its arguments are collected in the list. -- getOptions :: (Option a b) => b -> IO ([String],a) getOptions b = do args <- getArgs case parseOptions (b,"help" ?? "Display usage information") args of (helpTable, Left err) -> hPutStrLn stderr err >> hPutStrLn stderr helpTable >> exitFailure (helpTable,Right (_,(_,True))) -> do pname <- getProgName putStrLn $ "Usage: " ++ pname ++ " [OPTIONS] [ARGS]..." putStrLn helpTable exitWith ExitSuccess (_,Right (rs,(r,False))) -> return (rs,r) -- | Underlying option parser parseOptions :: (Option a b,Monad m) => b -- ^ The option parameters -> [String] -- ^ The raw options from the command line -> (String,m ([String],a)) -- ^ (help text,(non-option args, results) or fail if error found) parseOptions b args = ans where _st :: Monad m => m ([String],a) -> a _st _ = undefined ans = case ans' of Left s -> (helpTable,fail $ s) Right a -> (helpTable,return a) ans' = do let agi = argGetInfo' (_st ans') b (rs,as) <- pargs (matchFlatten agi) r <- matchingFmapM (f as) agi a <- argProcess' b r return (rs,a) f pm (ns,_) = return [ v | v@(x,_) <- pm , x `elem` ns ] pargs :: Monad m => [([String],ArgType)] -> m ([String],[(String,Maybe String)]) pargs xs = ans where ans = do let cu (x:_:_) = fail $ "Argument occurs more than once: " ++ showArgs x cu _ = return () mapM_ cu (group (sort [ x| (x,_) <- aa])) processArgs aa args (sa,la) = partition g aa g ([_],_) = True g _ = False aa = [ (y,at) | (ys,at) <- xs, y <- ys] helpTable = unlines $ buildTableLL $ map f (argHelp (_st ans') b) where f (xs,arg, help) = (" " ++ concat (intersperse ", " (map showArgs xs)) ++ ba arg,help) ba Nothing = "" ba (Just (True,s)) = ' ':s ba (Just (False,s)) = ' ':'[':s ++ "]" showArgs s | xs@(_:_:_) <- split (=='|') s = concat (intersperse ", " (map showArgs xs)) showArgs [c] = '-':c:[] showArgs xs = '-':'-':xs buildTableLL :: [(String,String)] -> [String] buildTableLL ps = map f ps where f (x,y) = x ++ replicate (bs - length x) ' ' ++ replicate 2 ' ' ++ y bs = maximum (map (length . fst) ps) processArgs :: Monad m => [(String,ArgType)] -> [String] -> m ([String],[(String,Maybe String)]) processArgs at args = h ([],[]) args where h (as,bs) ("--":rs) = return (reverse as ++ rs,reverse bs) h (as,bs) (('-':'-':argname):rs) | Just ArgNo <- ty = h (as,(argname,Nothing):bs) rs | Just ArgYes <- ty, (r:rs') <- rs = h (as,(argname,Just r):bs) rs' | Just ArgMaybe <- ty, (a,rs') <- hasArg rs = h (as,(argname,a):bs) rs' | otherwise = fail $ "Invalid Option: " ++ showArgs argname where ty = lookup argname at h cs (('-':as@(_:_)):rs) = z cs as where z (as,bs) (c:cs) | Just ArgNo <- ty = z (as,([c],Nothing):bs) cs | Just ArgYes <- ty = case cs of [] -> case rs of (x:rs') -> h (as,([c],Just x):bs) rs' [] -> fail $ "Option requires argument: " ++ showArgs [c] x -> h (as,([c],Just x):bs) rs | Just ArgMaybe <- ty, [] <- cs, (a,rs') <- hasArg rs = h (as,([c],a):bs) rs' | Just ArgMaybe <- ty = h (as,([c],Just cs):bs) rs | otherwise = fail $ "Invalid option: " ++ showArgs [c] where ty = lookup [c] at z cs [] = h cs rs h (as,bs) (r:rs) = h (r:as,bs) rs h (as,bs) [] = return (reverse as, reverse bs) hasArg [] = (Nothing,[]) hasArg rs@("--":_) = (Nothing,rs) hasArg rs@(('-':_):_) = (Nothing,rs) hasArg (r:rs) = (Just r,rs) class (Show a,Read a) => ArgOption a where argName :: a -> String showArg :: a -> String readArg :: Monad m => String -> m a argName _ = "ARG" showArg x = show x readArg x = case reads x of [(y,"")] -> return y (_ :: [(a,String)])-> fail $ "Invalid argument: " ++ argName (undefined :: a) ++ " expected" instance ArgOption String where showArg x = x readArg x = return x instance ArgOption Int where argName _ = "integer" instance ArgOption Integer where argName _ = "integer" instance ArgOption Double where argName _ = "floating" instance ArgOption Float where argName _ = "floating" instance (ArgOption a, ArgOption b) => ArgOption (Either a b) where argName (_ :: Either a b) | a1 /= a2 = a1 ++ " or " ++ a2 | otherwise = a1 where a1 = argName (_u :: a) a2 = argName (_u :: b) showArg (Left x) = showArg x showArg (Right x) = showArg x readArg s = case readArg s of Just x -> return $ Left x Nothing -> liftM Right $ readArg s _u = undefined instance Option Bool String where argGetInfo _ s = simpleGetInfo ArgNo s argProcess _ [] = return False argProcess _ _ = return True {- instance Option String (SHasDefault String) where argGetInfo _ (HasDefault s _) = simpleGetInfo ArgYes s argProcess (HasDefault s _) (_:_:_) = fail $ "Option may be specified at most once: " ++ showArg s argProcess _ [(_,Just x)] = return x argProcess (HasDefault _ b) [] = return b argHelp _ (HasDefault s b) = [([s],Just (True,b),"")] -} instance ArgOption a => Option (Maybe a) String where argGetInfo _ s = simpleGetInfo ArgYes s argProcess _ [] = return Nothing argProcess _ [(_,Just x)] = liftM Just $ readArg x argProcess s (_:_:_) = fail $ "Option may be specified at most once: " ++ showArgs s instance (ArgOption a) => Option a (HasDefault String a) where argGetInfo (_::a) (HasDefault s _) = simpleGetInfo ArgYes s argProcess (HasDefault s _) xs@(_:_:_) = fail $ "Option may be specified at most once: " ++ showArgs s argProcess _ [(_,Just x)] = readArg x argProcess (HasDefault _ b) [] = return b argHelp a (HasDefault s b) = [(split (=='|') s,Just (True,showArg b),"")] instance ArgOption a => Option [a] String where argGetInfo _ s = simpleGetInfo ArgYes s argProcess _ xs = mapM readArg $ [ x | (_,Just x) <- xs ] --argHelp a (HasDefault s b) = [(split (=='|') s,Just (True,showArg b),"")] instance Option a b => Option a (HasHelp b) where argGetInfo' a (HasHelp _ b) = argGetInfo' a b argProcess' (HasHelp _ b) m = argProcess' b m argHelp a (HasHelp x b) = [ (ns,a,x) | (ns,a,_) <- argHelp a b ] instance Option a b => Option a (NoHelp b) where argGetInfo' a (NoHelp b) = argGetInfo' a b argProcess' (NoHelp b) m = argProcess' b m argHelp _ _ = [] simpleGetInfo at s = (split (== '|') s,at) split :: (a -> Bool) -> [a] -> [[a]] split p s = case rest of [] -> [chunk] _:rest -> chunk : split p rest where (chunk, rest) = break p s instance (Option a c, Option b d) => Option (a,b) (c,d) where argGetInfo' (_::(a,b)) (x,y) = MatchSome [argGetInfo' (undefined :: a) x,argGetInfo' (undefined :: b) y] argProcess' (x,y) (MatchSome [x',y']) = liftM2 (,) (argProcess' x x') (argProcess' y y') argHelp (_::(a,b)) (x,y) = argHelp (undefined :: a) x ++ argHelp (undefined :: b) y {- TUPGEN! instance (#Tup Option #a #b) => Option (#Tup #a) (#Tup #b) where argGetInfo' (_::(#Tup #t)) (#Tup #x) = MatchSome [#List argGetInfo' (undefined :: #t) #x ] argProcess' (#Tup #x) (MatchSome [#List #y]) = do #Do #z <- argProcess' #x #y return (#Tup #z) argHelp (_::(#Tup #t)) (#Tup #x) = concat [#List argHelp (undefined :: #t) #x] -} -- tupgen 3 instance (Option a1 b1,Option a2 b2,Option a3 b3) => Option (a1,a2,a3) (b1,b2,b3) where argGetInfo' (_::(t1,t2,t3)) (x1,x2,x3) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ] argProcess' (x1,x2,x3) (MatchSome [y1,y2,y3]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 return (z1,z2,z3) argHelp (_::(t1,t2,t3)) (x1,x2,x3) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3] -- tupgen 4 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4) => Option (a1,a2,a3,a4) (b1,b2,b3,b4) where argGetInfo' (_::(t1,t2,t3,t4)) (x1,x2,x3,x4) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ] argProcess' (x1,x2,x3,x4) (MatchSome [y1,y2,y3,y4]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 return (z1,z2,z3,z4) argHelp (_::(t1,t2,t3,t4)) (x1,x2,x3,x4) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4] -- tupgen 5 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5) => Option (a1,a2,a3,a4,a5) (b1,b2,b3,b4,b5) where argGetInfo' (_::(t1,t2,t3,t4,t5)) (x1,x2,x3,x4,x5) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ] argProcess' (x1,x2,x3,x4,x5) (MatchSome [y1,y2,y3,y4,y5]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 return (z1,z2,z3,z4,z5) argHelp (_::(t1,t2,t3,t4,t5)) (x1,x2,x3,x4,x5) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5] -- tupgen 6 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6) => Option (a1,a2,a3,a4,a5,a6) (b1,b2,b3,b4,b5,b6) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6)) (x1,x2,x3,x4,x5,x6) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ] argProcess' (x1,x2,x3,x4,x5,x6) (MatchSome [y1,y2,y3,y4,y5,y6]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 return (z1,z2,z3,z4,z5,z6) argHelp (_::(t1,t2,t3,t4,t5,t6)) (x1,x2,x3,x4,x5,x6) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6] -- tupgen 7 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7) => Option (a1,a2,a3,a4,a5,a6,a7) (b1,b2,b3,b4,b5,b6,b7) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7)) (x1,x2,x3,x4,x5,x6,x7) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ] argProcess' (x1,x2,x3,x4,x5,x6,x7) (MatchSome [y1,y2,y3,y4,y5,y6,y7]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 return (z1,z2,z3,z4,z5,z6,z7) argHelp (_::(t1,t2,t3,t4,t5,t6,t7)) (x1,x2,x3,x4,x5,x6,x7) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7] -- tupgen 8 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8) => Option (a1,a2,a3,a4,a5,a6,a7,a8) (b1,b2,b3,b4,b5,b6,b7,b8) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8)) (x1,x2,x3,x4,x5,x6,x7,x8) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 return (z1,z2,z3,z4,z5,z6,z7,z8) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8)) (x1,x2,x3,x4,x5,x6,x7,x8) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8] -- tupgen 9 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9) (b1,b2,b3,b4,b5,b6,b7,b8,b9) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9)) (x1,x2,x3,x4,x5,x6,x7,x8,x9) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 return (z1,z2,z3,z4,z5,z6,z7,z8,z9) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9)) (x1,x2,x3,x4,x5,x6,x7,x8,x9) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9] -- tupgen 10 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10] -- tupgen 11 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10,Option a11 b11) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ,argGetInfo' (undefined :: t11) x11 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 z11 <- argProcess' x11 y11 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10,z11) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10,argHelp (undefined :: t11) x11] -- tupgen 12 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10,Option a11 b11,Option a12 b12) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ,argGetInfo' (undefined :: t11) x11 ,argGetInfo' (undefined :: t12) x12 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11,y12]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 z11 <- argProcess' x11 y11 z12 <- argProcess' x12 y12 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10,z11,z12) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10,argHelp (undefined :: t11) x11,argHelp (undefined :: t12) x12] -- tupgen 13 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10,Option a11 b11,Option a12 b12,Option a13 b13) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12,a13) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12,b13) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ,argGetInfo' (undefined :: t11) x11 ,argGetInfo' (undefined :: t12) x12 ,argGetInfo' (undefined :: t13) x13 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11,y12,y13]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 z11 <- argProcess' x11 y11 z12 <- argProcess' x12 y12 z13 <- argProcess' x13 y13 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10,z11,z12,z13) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10,argHelp (undefined :: t11) x11,argHelp (undefined :: t12) x12,argHelp (undefined :: t13) x13] -- tupgen 14 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10,Option a11 b11,Option a12 b12,Option a13 b13,Option a14 b14) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12,a13,a14) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12,b13,b14) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ,argGetInfo' (undefined :: t11) x11 ,argGetInfo' (undefined :: t12) x12 ,argGetInfo' (undefined :: t13) x13 ,argGetInfo' (undefined :: t14) x14 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11,y12,y13,y14]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 z11 <- argProcess' x11 y11 z12 <- argProcess' x12 y12 z13 <- argProcess' x13 y13 z14 <- argProcess' x14 y14 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10,z11,z12,z13,z14) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10,argHelp (undefined :: t11) x11,argHelp (undefined :: t12) x12,argHelp (undefined :: t13) x13,argHelp (undefined :: t14) x14] -- tupgen 15 instance (Option a1 b1,Option a2 b2,Option a3 b3,Option a4 b4,Option a5 b5,Option a6 b6,Option a7 b7,Option a8 b8,Option a9 b9,Option a10 b10,Option a11 b11,Option a12 b12,Option a13 b13,Option a14 b14,Option a15 b15) => Option (a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12,a13,a14,a15) (b1,b2,b3,b4,b5,b6,b7,b8,b9,b10,b11,b12,b13,b14,b15) where argGetInfo' (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14,t15)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15) = MatchSome [argGetInfo' (undefined :: t1) x1 ,argGetInfo' (undefined :: t2) x2 ,argGetInfo' (undefined :: t3) x3 ,argGetInfo' (undefined :: t4) x4 ,argGetInfo' (undefined :: t5) x5 ,argGetInfo' (undefined :: t6) x6 ,argGetInfo' (undefined :: t7) x7 ,argGetInfo' (undefined :: t8) x8 ,argGetInfo' (undefined :: t9) x9 ,argGetInfo' (undefined :: t10) x10 ,argGetInfo' (undefined :: t11) x11 ,argGetInfo' (undefined :: t12) x12 ,argGetInfo' (undefined :: t13) x13 ,argGetInfo' (undefined :: t14) x14 ,argGetInfo' (undefined :: t15) x15 ] argProcess' (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15) (MatchSome [y1,y2,y3,y4,y5,y6,y7,y8,y9,y10,y11,y12,y13,y14,y15]) = do z1 <- argProcess' x1 y1 z2 <- argProcess' x2 y2 z3 <- argProcess' x3 y3 z4 <- argProcess' x4 y4 z5 <- argProcess' x5 y5 z6 <- argProcess' x6 y6 z7 <- argProcess' x7 y7 z8 <- argProcess' x8 y8 z9 <- argProcess' x9 y9 z10 <- argProcess' x10 y10 z11 <- argProcess' x11 y11 z12 <- argProcess' x12 y12 z13 <- argProcess' x13 y13 z14 <- argProcess' x14 y14 z15 <- argProcess' x15 y15 return (z1,z2,z3,z4,z5,z6,z7,z8,z9,z10,z11,z12,z13,z14,z15) argHelp (_::(t1,t2,t3,t4,t5,t6,t7,t8,t9,t10,t11,t12,t13,t14,t15)) (x1,x2,x3,x4,x5,x6,x7,x8,x9,x10,x11,x12,x13,x14,x15) = concat [argHelp (undefined :: t1) x1,argHelp (undefined :: t2) x2,argHelp (undefined :: t3) x3,argHelp (undefined :: t4) x4,argHelp (undefined :: t5) x5,argHelp (undefined :: t6) x6,argHelp (undefined :: t7) x7,argHelp (undefined :: t8) x8,argHelp (undefined :: t9) x9,argHelp (undefined :: t10) x10,argHelp (undefined :: t11) x11,argHelp (undefined :: t12) x12,argHelp (undefined :: t13) x13,argHelp (undefined :: t14) x14,argHelp (undefined :: t15) x15]