{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Biobase.ExtSS.Export where

import Data.ByteString.Char8 as BS
import Data.Iteratee as I
import Data.Iteratee.Char as I
import Data.Iteratee.ListLike as I
import Prelude as P hiding (sequence)
import Text.Printf

import Biobase.ExtSS



-- | Given a list of 'ExtSS' elements, transform into a bytestring.

eneeByteString :: (Monad m) => Enumeratee [ExtSS] ByteString m a
eneeByteString = mapChunks (BS.unlines . P.map f) where
  f :: ExtSS -> ByteString
  f ExtSS{..} =  BS.unlines
              $  P.map (BS.append "#") comments
              ++ [sequence]
              ++ [structure]
              ++ P.map (\(i,j,cww) -> BS.pack $ printf " %4d %4d %3s") detailed