{-| Simulate reagent 'kits', i.e. tack on adapters etc -} {-# LANGUAGE DeriveDataTypeable #-} module KitSim where import Version import System.Console.CmdArgs import System.IO import qualified Data.ByteString.Lazy.Char8 as B import Bio.Core.Sequence import Bio.Sequence.Fasta main :: IO () main = do cf <- cmdArgs conf let reader = case input cf of "-" -> hReadFasta stdin f -> readFasta f writer = case output cf of "-" -> hWriteFasta stdout f -> writeFasta f apply cf `fmap` reader >>= writer apply :: Conf -> [Sequence] -> [Sequence] apply c = map apply1 where apply1 (Seq s (SeqData d) _) = Seq s (SeqData $ B.concat [k,d,a]) Nothing k = B.pack (key c) a = B.pack (adapter c) conf :: Conf conf = Conf { key = "TCAG" &= help "Sequence for initial key" &= typ "String" , adapter = "ctgagactgccaaggcacacagggggatagg" &= help "Sequence for B-adapter" &= typ "String" , input = "-" &= args &= typFile , output = "-" &= help "Output file" &= typFile } &= program "kitsim" &= summary ("kitsim"++version) &= details ["Simulates the sequencing kit by tacking on the initial key" ,"(really the end of the A-adapter) and B-adapter"] data Conf = Conf { key, adapter :: String, input, output :: FilePath } deriving (Data,Typeable)