{-# Language DeriveGeneric #-}
module Biobase.Fasta.Types where
import Control.DeepSeq
import Control.Lens
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Lazy.Char8 as B
import Data.Data
import GHC.Generics
import Biobase.Types.NucleotideSequence
import Biobase.Types.AminoAcidSequence
data Fasta = Fasta { fastaHeader :: B.ByteString, fastaSequence :: B.ByteString }
deriving (Eq)
newtype RawFastaEntry = RawFastaEntry { _rawFastaEntry :: ByteString }
deriving (Show,Eq,Ord,Typeable)
data StreamEvent
= StreamHeader { streamHeader :: !ByteString, streamLines :: !LineInfo }
| StreamFasta { streamFasta :: !ByteString, prevStreamFasta :: !ByteString, streamLines :: !LineInfo, streamHeader :: !ByteString }
deriving (Show,Eq,Ord,Typeable,Generic)
instance NFData StreamEvent
data LineInfo = LineInfo
{ firstLine :: !Int
, firstCol :: !Int
, lastLine :: !Int
, lastCol :: !Int
, firstIndex :: !Int
}
deriving (Show,Eq,Ord,Typeable,Generic)
instance NFData LineInfo