{-# LANGUAGE DeriveDataTypeable    #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE StrictData            #-}
{-# LANGUAGE TypeFamilies          #-}

-- |
-- Module      :  Data.BAM.Version1_6.Base
-- Copyright   :  (c) Matthew Mosior 2024
-- License     :  BSD-style
-- Maintainer  :  mattm.github@gmail.com
-- Portability :  portable
--
-- = Description
--
-- This library enables the decoding/encoding of SAM, BAM and CRAM file formats.

module Data.BAM.Version1_6.Base ( -- * BAM_V1_6 version 1.6 data type
                                  BAM_V1_6(..)
                                ) where

import Data.BAM.Version1_6.BGZFBlock

import Data.Data
import Data.Sequence
import Generics.Deriving.Base

-- | Custom @"BAM_V1_6"@ (BAM version 1.6) newtype.
--
-- See the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
newtype BAM_V1_6 = BAM_V1_6
  { BAM_V1_6 -> Seq BAM_V1_6_BGZFBlock
bam_v1_6 :: Seq BAM_V1_6_BGZFBlock -- ^ Sequence holding all
                                       -- BGZF blocks of data
                                       -- within the BAM file.
  } deriving ((forall x. BAM_V1_6 -> Rep BAM_V1_6 x)
-> (forall x. Rep BAM_V1_6 x -> BAM_V1_6) -> Generic BAM_V1_6
forall x. Rep BAM_V1_6 x -> BAM_V1_6
forall x. BAM_V1_6 -> Rep BAM_V1_6 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BAM_V1_6 -> Rep BAM_V1_6 x
from :: forall x. BAM_V1_6 -> Rep BAM_V1_6 x
$cto :: forall x. Rep BAM_V1_6 x -> BAM_V1_6
to :: forall x. Rep BAM_V1_6 x -> BAM_V1_6
Generic,Typeable)

instance Eq BAM_V1_6 where
  BAM_V1_6 Seq BAM_V1_6_BGZFBlock
bam_v1_61 == :: BAM_V1_6 -> BAM_V1_6 -> Bool
==
    BAM_V1_6 Seq BAM_V1_6_BGZFBlock
bam_v1_62 =
      Seq BAM_V1_6_BGZFBlock
bam_v1_61 Seq BAM_V1_6_BGZFBlock -> Seq BAM_V1_6_BGZFBlock -> Bool
forall a. Eq a => a -> a -> Bool
== Seq BAM_V1_6_BGZFBlock
bam_v1_62

instance Show BAM_V1_6 where
  show :: BAM_V1_6 -> String
show (BAM_V1_6 Seq BAM_V1_6_BGZFBlock
bam
       ) =
    String
"BAM_V1_6 { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"bam_v1_6 = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Seq BAM_V1_6_BGZFBlock -> String
forall a. Show a => a -> String
show Seq BAM_V1_6_BGZFBlock
bam)    String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"