module Data.Fasta.Text.Types where
import qualified Data.Text as T
import qualified Data.Map as M
data FastaSequence = FastaSequence { fastaHeader :: T.Text
, fastaSeq :: T.Text
} deriving (Eq, Ord, Show)
type Clone = FastaSequence
type Germline = FastaSequence
type Codon = T.Text
type CloneMap = M.Map (Int, Germline) [Clone]
class ShowFasta a where
showFasta :: a -> T.Text
instance ShowFasta FastaSequence where
showFasta FastaSequence {fastaHeader = x, fastaSeq = y} = T.concat [ ">"
, x
, "\n"
, y ]