module Options where import System.Environment (getArgs) import System.Console.GetOpt import System (exitWith,ExitCode(..)) import Control.Monad -- import Bio.Util (countIO) getOptions :: IO Options getOptions = do as <- getArgs let (optf,non,err) = getOpt Permute options as when (not (null err && null non)) $ error (usage err) if null as then normalUsage else parseargs optf normalUsage :: IO a normalUsage = do putStrLn $ usageInfo (usagemsg++synopsis) options exitWith ExitSuccess usage :: [String] -> String usage errs = usageInfo (concat errs ++ usagemsg) options usagemsg, synopsis :: String usagemsg = "Usage: korfu -i -x [-R ] [-C ]\n" synopsis = "Characterize ESTs using BLASTX hits and sequence heuristics.\n" data Options = Opts { redir_out, cds_out :: FilePath , default_fwd :: Bool , gen_all :: Bool , fasta,blastx :: FilePath } options :: [OptDescr (Options -> IO Options)] options = [ -- Output options Option ['R'] ["redir-out"] (ReqArg (\arg opt -> return (if gen_all opt then incompat else opt { redir_out = arg })) "File") "File for sequence output,\nreoriented to predicted 5' to 3' direction." , Option ['C'] ["cds-out"] (ReqArg (\arg opt -> return opt { cds_out = arg }) "File") "File for predicted CDS output." -- todo: -- , Option ['r'] ["reverse-default"] (NoArg (\opt -> return opt { default_fwd = False })) -- "Reverse sequences without good orientation predictions" , Option [] ["all"] (NoArg (\opt -> return (if null (blastx opt) then opt { gen_all = True } else incompat))) "Generate all frames" -- Input options , Option ['i'] ["sequence-file"] (ReqArg (\arg opt -> return opt { fasta = arg }) "File") "File for sequence input (Fasta-format)." , Option ['x'] ["blast-xml-file"] (ReqArg (\arg opt -> return (if gen_all opt then incompat else opt { blastx = arg })) "File") "File for Blastx result input\n(XML-format, use 'blastall -m 7')." -- Other options , Option ['h'] ["help"] (NoArg (\_ -> normalUsage)) "Print usage information." ] where incompat = error "'--all' is incompatible with '-x' and '-R'." defaultopts :: Options defaultopts = Opts { redir_out = "" , cds_out = "" , default_fwd = True , gen_all = False , fasta = error "No sequence input specified" , blastx = "" } parseargs :: [Options -> IO Options] -> IO Options parseargs args = foldl (>>=) (return defaultopts) args >>= verify where verify = return . id