-- | New version, using BlastX results to determine ORFs module Main where import System.IO import Blastx import Options import Bio.Sequence import Bio.Alignment.BlastFlat import Control.Monad (when) import Data.Maybe main :: IO () main = do opts <- getOptions ss <- readFasta $ fasta opts if gen_all opts then do case cds_out opts of "" -> error "No output specified" "-" -> hWriteFasta stdout $ concatMap all_frames ss cf -> writeFasta cf $ concatMap all_frames ss else do bs <- readXML $ blastx opts h <- case redir_out opts of "" -> return Nothing "-" -> return (Just stdout) rf -> openFile rf WriteMode >>= \x -> return (Just x) g <- case cds_out opts of "" -> return Nothing "-" -> return (Just stdout) cf -> openFile cf WriteMode >>= \x -> return (Just x) let my_process s = do when (isJust h) $ process genFasta (fromJust h) s when (isJust g) $ process genCDS (fromJust g) s mapM_ my_process (frames ss bs) when (isJust g) $ hClose (fromJust g) when (isJust h) $ hClose (fromJust h) all_frames :: Sequence -> [Sequence] all_frames s = map (\i -> (Seq (fromStr (toStr (seqlabel s)++"_F+"++show i)) (toIUPAC $ translate s i) Nothing)) [0,1,2] ++ map (\i -> (Seq (fromStr (toStr (seqlabel s)++"_F-"++show i)) (toIUPAC $ translate (revcompl s) i) Nothing)) [0,1,2] process :: (a -> [Sequence]) -> Handle -> a -> IO () process fmt h = hWriteFasta h . fmt