-- | Tabulate -- Data structure for tables consisting of cells with various alignments. -- For building more generic rendering of alignments module Tabulate where import Prelude hiding (words) import Bio.Alignment.BlastData import Data.ByteString.Lazy.Char8 (ByteString,words) import Data.List (sortBy) type Table = (ByteString,Int,[Row]) type Row = (ByteString,[Cell]) data Cell = Cell { wd :: Int, color :: Int, frame :: Maybe Aux } deriving Show tabulate :: BlastRecord -> Table tabulate b = (head $ words $ query b, qlength b, map (row (qlength b)) (hits b)) row :: Int -> BlastHit -> Row row wtot h = (head $ words $ subject h, go 0 $ sort_matches $ matches h) where sort_matches = sortBy (\m1 m2 -> compare (min (q_from m1) (q_to m1)) (min (q_from m2) (q_to m2))) go :: Int -> [BlastMatch] -> [Cell] go p [] = [Cell (wtot-p) 0 Nothing] go p (b:bs') = let (f',t') = (q_from b,q_to b) (f,t) = if f'