-- ace2fa -- Read an ACE file, output in Fasta format -- (for importing into seaview) module Main where import Prelude hiding (reads) import Bio.Alignment.ACE import Bio.Sequence import qualified Data.ByteString.Lazy.Char8 as B import System.SimpleArgs (getArgs) import System.IO main :: IO () main = do a <- readACE =<< getArgs mapM_ (\ss -> writeFasta (B.unpack $ seqlabel $ head ss) ss) (map pad_all $ concat a) pad_all :: Assembly -> [Sequence] pad_all asm = pad 21 (contig asm) : map padRead (reads asm) where padRead (off,_dir,sq,gs) = pad (20+off) (sq,gs) -- note: they are already complemented -- generate a sequence with '-' for gaps pad :: Offset -> (Sequence,Gaps) -> Sequence pad off (Seq n s _,gs) = let s' = (if off < 0 then B.drop (negate off) else B.append (B.replicate off '-')) (insertGaps '-' (s,gs)) in (Seq n s' Nothing)