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

-- |
-- Module      :  Data.SAM.Version1_6.Header.RG
-- Copyright   :  (c) Matthew Mosior 2023
-- 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.SAM.Version1_6.Header.RG ( -- * SAM version 1.6 Read group data type
                                       SAM_V1_6_Read_Group(..),
                                       -- * SAM version 1.6 Read group data types
                                       SAM_V1_6_Read_Group_Identifier(..),
                                       SAM_V1_6_Read_Group_Barcode_Sequence(..),
                                       SAM_V1_6_Read_Group_Sequencing_Center(..),
                                       SAM_V1_6_Read_Group_Description(..),
                                       SAM_V1_6_Read_Group_Run_Date(..),
                                       SAM_V1_6_Read_Group_Flow_Order(..),
                                       SAM_V1_6_Read_Group_Key_Sequence(..),
                                       SAM_V1_6_Read_Group_Library(..),
                                       SAM_V1_6_Read_Group_Programs(..),
                                       SAM_V1_6_Read_Group_Predicted_Median_Insert_Size(..),
                                       SAM_V1_6_Read_Group_Platform(..),
                                       SAM_V1_6_Read_Group_Platform_Model(..),
                                       SAM_V1_6_Read_Group_Platform_Unit(..),
                                       SAM_V1_6_Read_Group_Sample(..)
                                     ) where

import Data.ByteString
import Data.Data
import Generics.Deriving.Base

-- | Custom SAM (version 1.6) @"SAM_V1_6_Read_Group"@ data type.
--
-- See section 1.3 of the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
data SAM_V1_6_Read_Group = SAM_V1_6_Read_Group { SAM_V1_6_Read_Group -> SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifier                   :: SAM_V1_6_Read_Group_Identifier
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence             :: Maybe SAM_V1_6_Read_Group_Barcode_Sequence
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center            :: Maybe SAM_V1_6_Read_Group_Sequencing_Center
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description                  :: Maybe SAM_V1_6_Read_Group_Description
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date                     :: Maybe SAM_V1_6_Read_Group_Run_Date
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order                   :: Maybe SAM_V1_6_Read_Group_Flow_Order
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence                 :: Maybe SAM_V1_6_Read_Group_Key_Sequence
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library                      :: Maybe SAM_V1_6_Read_Group_Library
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs                     :: Maybe SAM_V1_6_Read_Group_Programs
                                               , SAM_V1_6_Read_Group
-> Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size :: Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform                     :: Maybe SAM_V1_6_Read_Group_Platform
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model               :: Maybe SAM_V1_6_Read_Group_Platform_Model
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit                :: Maybe SAM_V1_6_Read_Group_Platform_Unit
                                               , SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample                       :: Maybe SAM_V1_6_Read_Group_Sample
                                               }
  deriving ((forall x. SAM_V1_6_Read_Group -> Rep SAM_V1_6_Read_Group x)
-> (forall x. Rep SAM_V1_6_Read_Group x -> SAM_V1_6_Read_Group)
-> Generic SAM_V1_6_Read_Group
forall x. Rep SAM_V1_6_Read_Group x -> SAM_V1_6_Read_Group
forall x. SAM_V1_6_Read_Group -> Rep SAM_V1_6_Read_Group x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SAM_V1_6_Read_Group -> Rep SAM_V1_6_Read_Group x
from :: forall x. SAM_V1_6_Read_Group -> Rep SAM_V1_6_Read_Group x
$cto :: forall x. Rep SAM_V1_6_Read_Group x -> SAM_V1_6_Read_Group
to :: forall x. Rep SAM_V1_6_Read_Group x -> SAM_V1_6_Read_Group
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group where
  SAM_V1_6_Read_Group SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifier1
                      Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence1
                      Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center1
                      Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description1
                      Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date1
                      Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order1
                      Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence1
                      Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library1
                      Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs1
                      Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size1
                      Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform1
                      Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model1
                      Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit1
                      Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample1 == :: SAM_V1_6_Read_Group -> SAM_V1_6_Read_Group -> Bool
== SAM_V1_6_Read_Group SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifier2
                                                                         Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence2
                                                                         Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center2
                                                                         Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description2
                                                                         Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date2
                                                                         Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order2
                                                                         Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence2
                                                                         Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library2
                                                                         Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs2
                                                                         Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size2
                                                                         Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform2
                                                                         Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model2
                                                                         Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit2
                                                                         Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample2 = SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifier1                    SAM_V1_6_Read_Group_Identifier
-> SAM_V1_6_Read_Group_Identifier -> Bool
forall a. Eq a => a -> a -> Bool
== SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifier2                    Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence1             Maybe SAM_V1_6_Read_Group_Barcode_Sequence
-> Maybe SAM_V1_6_Read_Group_Barcode_Sequence -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence2             Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center1            Maybe SAM_V1_6_Read_Group_Sequencing_Center
-> Maybe SAM_V1_6_Read_Group_Sequencing_Center -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center2            Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description1                  Maybe SAM_V1_6_Read_Group_Description
-> Maybe SAM_V1_6_Read_Group_Description -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description2                  Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date1                     Maybe SAM_V1_6_Read_Group_Run_Date
-> Maybe SAM_V1_6_Read_Group_Run_Date -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date2                     Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order1                   Maybe SAM_V1_6_Read_Group_Flow_Order
-> Maybe SAM_V1_6_Read_Group_Flow_Order -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order2                   Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence1                 Maybe SAM_V1_6_Read_Group_Key_Sequence
-> Maybe SAM_V1_6_Read_Group_Key_Sequence -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence2                 Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library1                      Maybe SAM_V1_6_Read_Group_Library
-> Maybe SAM_V1_6_Read_Group_Library -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library2                      Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs1                     Maybe SAM_V1_6_Read_Group_Programs
-> Maybe SAM_V1_6_Read_Group_Programs -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs2                     Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size1 Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
-> Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size2 Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform1                     Maybe SAM_V1_6_Read_Group_Platform
-> Maybe SAM_V1_6_Read_Group_Platform -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform2                     Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model1               Maybe SAM_V1_6_Read_Group_Platform_Model
-> Maybe SAM_V1_6_Read_Group_Platform_Model -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model2               Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit1                Maybe SAM_V1_6_Read_Group_Platform_Unit
-> Maybe SAM_V1_6_Read_Group_Platform_Unit -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit2                Bool -> Bool -> Bool
&&
                                                                                                       Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample1                       Maybe SAM_V1_6_Read_Group_Sample
-> Maybe SAM_V1_6_Read_Group_Sample -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample2

instance Show SAM_V1_6_Read_Group where
  show :: SAM_V1_6_Read_Group -> String
show (SAM_V1_6_Read_Group SAM_V1_6_Read_Group_Identifier
group_identifier
                            Maybe SAM_V1_6_Read_Group_Barcode_Sequence
barcode_sequence
                            Maybe SAM_V1_6_Read_Group_Sequencing_Center
sequencing_center
                            Maybe SAM_V1_6_Read_Group_Description
description
                            Maybe SAM_V1_6_Read_Group_Run_Date
run_date
                            Maybe SAM_V1_6_Read_Group_Flow_Order
flow_order
                            Maybe SAM_V1_6_Read_Group_Key_Sequence
key_sequence
                            Maybe SAM_V1_6_Read_Group_Library
library
                            Maybe SAM_V1_6_Read_Group_Programs
programs
                            Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
predicted_median_insert_size
                            Maybe SAM_V1_6_Read_Group_Platform
platform
                            Maybe SAM_V1_6_Read_Group_Platform_Model
platform_model
                            Maybe SAM_V1_6_Read_Group_Platform_Unit
platform_unit
                            Maybe SAM_V1_6_Read_Group_Sample
sample
       ) =
    String
"SAM_V1_6_Read_Group { "                                      String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_identifier = "                           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (SAM_V1_6_Read_Group_Identifier -> String
forall a. Show a => a -> String
show SAM_V1_6_Read_Group_Identifier
group_identifier)                                       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_barcode_sequence = "                  String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Barcode_Sequence -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Barcode_Sequence
barcode_sequence)                                       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_sequencing_center = "                 String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Sequencing_Center -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Sequencing_Center
sequencing_center)                                      String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_description = "                       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Description -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Description
description)                                            String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_run_date = "                          String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Run_Date -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Run_Date
run_date)                                               String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_flow_order = "                        String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Flow_Order -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Flow_Order
flow_order)                                             String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_key_sequence = "                      String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Key_Sequence -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Key_Sequence
key_sequence)                                           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_library = "                           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Library -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Library
library)                                                String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_programs = "                          String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Programs -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Programs
programs)                                               String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_show_predicted_median_insert_size = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
predicted_median_insert_size)                           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_platform = "                          String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Platform -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Platform
platform)                                               String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_platform_model = "                    String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Platform_Model -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Platform_Model
platform_model)                                         String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_platform_unit = "                     String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Platform_Unit -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Platform_Unit
platform_unit)                                          String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group_sample = "                            String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Read_Group_Sample -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Read_Group_Sample
sample)                                                 String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | ID tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Identifier = SAM_V1_6_Read_Group_Identifier { SAM_V1_6_Read_Group_Identifier -> ByteString
sam_v1_6_read_group_identifier_value :: ByteString
                                                                        }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Identifier
 -> Rep SAM_V1_6_Read_Group_Identifier x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Identifier x
    -> SAM_V1_6_Read_Group_Identifier)
-> Generic SAM_V1_6_Read_Group_Identifier
forall x.
Rep SAM_V1_6_Read_Group_Identifier x
-> SAM_V1_6_Read_Group_Identifier
forall x.
SAM_V1_6_Read_Group_Identifier
-> Rep SAM_V1_6_Read_Group_Identifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Identifier
-> Rep SAM_V1_6_Read_Group_Identifier x
from :: forall x.
SAM_V1_6_Read_Group_Identifier
-> Rep SAM_V1_6_Read_Group_Identifier x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Identifier x
-> SAM_V1_6_Read_Group_Identifier
to :: forall x.
Rep SAM_V1_6_Read_Group_Identifier x
-> SAM_V1_6_Read_Group_Identifier
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Identifier where
  SAM_V1_6_Read_Group_Identifier ByteString
sam_v1_6_read_group_identifier_value1 == :: SAM_V1_6_Read_Group_Identifier
-> SAM_V1_6_Read_Group_Identifier -> Bool
== SAM_V1_6_Read_Group_Identifier ByteString
sam_v1_6_read_group_identifier_value2 = ByteString
sam_v1_6_read_group_identifier_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_identifier_value2

instance Show SAM_V1_6_Read_Group_Identifier where
  show :: SAM_V1_6_Read_Group_Identifier -> String
show (SAM_V1_6_Read_Group_Identifier ByteString
value) =
    String
"SAM_V1_6_Read_Group_Identifier { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_identifier_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                              String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | BC tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Barcode_Sequence = SAM_V1_6_Read_Group_Barcode_Sequence { SAM_V1_6_Read_Group_Barcode_Sequence -> ByteString
sam_v1_6_read_group_barcode_sequence_value :: ByteString
                                                                                    }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Barcode_Sequence
 -> Rep SAM_V1_6_Read_Group_Barcode_Sequence x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Barcode_Sequence x
    -> SAM_V1_6_Read_Group_Barcode_Sequence)
-> Generic SAM_V1_6_Read_Group_Barcode_Sequence
forall x.
Rep SAM_V1_6_Read_Group_Barcode_Sequence x
-> SAM_V1_6_Read_Group_Barcode_Sequence
forall x.
SAM_V1_6_Read_Group_Barcode_Sequence
-> Rep SAM_V1_6_Read_Group_Barcode_Sequence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Barcode_Sequence
-> Rep SAM_V1_6_Read_Group_Barcode_Sequence x
from :: forall x.
SAM_V1_6_Read_Group_Barcode_Sequence
-> Rep SAM_V1_6_Read_Group_Barcode_Sequence x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Barcode_Sequence x
-> SAM_V1_6_Read_Group_Barcode_Sequence
to :: forall x.
Rep SAM_V1_6_Read_Group_Barcode_Sequence x
-> SAM_V1_6_Read_Group_Barcode_Sequence
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Barcode_Sequence where
  SAM_V1_6_Read_Group_Barcode_Sequence ByteString
sam_v1_6_read_group_barcode_sequence_value1 == :: SAM_V1_6_Read_Group_Barcode_Sequence
-> SAM_V1_6_Read_Group_Barcode_Sequence -> Bool
== SAM_V1_6_Read_Group_Barcode_Sequence ByteString
sam_v1_6_read_group_barcode_sequence_value2 = ByteString
sam_v1_6_read_group_barcode_sequence_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_barcode_sequence_value2

instance Show SAM_V1_6_Read_Group_Barcode_Sequence where
  show :: SAM_V1_6_Read_Group_Barcode_Sequence -> String
show (SAM_V1_6_Read_Group_Barcode_Sequence ByteString
value) =
    String
"SAM_V1_6_Read_Group_Barcode_Sequence { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_barcode_sequence_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                    String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | CN tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Sequencing_Center = SAM_V1_6_Read_Group_Sequencing_Center { SAM_V1_6_Read_Group_Sequencing_Center -> ByteString
sam_v1_6_read_group_sequencing_center_value :: ByteString
                                                                                      }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Sequencing_Center
 -> Rep SAM_V1_6_Read_Group_Sequencing_Center x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Sequencing_Center x
    -> SAM_V1_6_Read_Group_Sequencing_Center)
-> Generic SAM_V1_6_Read_Group_Sequencing_Center
forall x.
Rep SAM_V1_6_Read_Group_Sequencing_Center x
-> SAM_V1_6_Read_Group_Sequencing_Center
forall x.
SAM_V1_6_Read_Group_Sequencing_Center
-> Rep SAM_V1_6_Read_Group_Sequencing_Center x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Sequencing_Center
-> Rep SAM_V1_6_Read_Group_Sequencing_Center x
from :: forall x.
SAM_V1_6_Read_Group_Sequencing_Center
-> Rep SAM_V1_6_Read_Group_Sequencing_Center x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Sequencing_Center x
-> SAM_V1_6_Read_Group_Sequencing_Center
to :: forall x.
Rep SAM_V1_6_Read_Group_Sequencing_Center x
-> SAM_V1_6_Read_Group_Sequencing_Center
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Sequencing_Center where
  SAM_V1_6_Read_Group_Sequencing_Center ByteString
sam_v1_6_read_group_sequencing_center_value1 == :: SAM_V1_6_Read_Group_Sequencing_Center
-> SAM_V1_6_Read_Group_Sequencing_Center -> Bool
== SAM_V1_6_Read_Group_Sequencing_Center ByteString
sam_v1_6_read_group_sequencing_center_value2 = ByteString
sam_v1_6_read_group_sequencing_center_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_sequencing_center_value2

instance Show SAM_V1_6_Read_Group_Sequencing_Center where
  show :: SAM_V1_6_Read_Group_Sequencing_Center -> String
show (SAM_V1_6_Read_Group_Sequencing_Center ByteString
value) =
    String
"SAM_V1_6_Read_Group_Sequencing_Center { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_sequencing_center_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                     String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | DS tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Description = SAM_V1_6_Read_Group_Description { SAM_V1_6_Read_Group_Description -> ByteString
sam_v1_6_read_group_description_value :: ByteString
                                                                          }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Description
 -> Rep SAM_V1_6_Read_Group_Description x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Description x
    -> SAM_V1_6_Read_Group_Description)
-> Generic SAM_V1_6_Read_Group_Description
forall x.
Rep SAM_V1_6_Read_Group_Description x
-> SAM_V1_6_Read_Group_Description
forall x.
SAM_V1_6_Read_Group_Description
-> Rep SAM_V1_6_Read_Group_Description x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Description
-> Rep SAM_V1_6_Read_Group_Description x
from :: forall x.
SAM_V1_6_Read_Group_Description
-> Rep SAM_V1_6_Read_Group_Description x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Description x
-> SAM_V1_6_Read_Group_Description
to :: forall x.
Rep SAM_V1_6_Read_Group_Description x
-> SAM_V1_6_Read_Group_Description
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Description where
  SAM_V1_6_Read_Group_Description ByteString
sam_v1_6_read_group_description_value1 == :: SAM_V1_6_Read_Group_Description
-> SAM_V1_6_Read_Group_Description -> Bool
== SAM_V1_6_Read_Group_Description ByteString
sam_v1_6_read_group_description_value2 = ByteString
sam_v1_6_read_group_description_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_description_value2

instance Show SAM_V1_6_Read_Group_Description where
  show :: SAM_V1_6_Read_Group_Description -> String
show (SAM_V1_6_Read_Group_Description ByteString
value) =
    String
"SAM_V1_6_Read_Group_Description { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_description_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                               String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | DT tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Run_Date = SAM_V1_6_Read_Group_Run_Date { SAM_V1_6_Read_Group_Run_Date -> ByteString
sam_v1_6_read_group_run_date_value :: ByteString
                                                                    }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Run_Date -> Rep SAM_V1_6_Read_Group_Run_Date x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Run_Date x -> SAM_V1_6_Read_Group_Run_Date)
-> Generic SAM_V1_6_Read_Group_Run_Date
forall x.
Rep SAM_V1_6_Read_Group_Run_Date x -> SAM_V1_6_Read_Group_Run_Date
forall x.
SAM_V1_6_Read_Group_Run_Date -> Rep SAM_V1_6_Read_Group_Run_Date x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Run_Date -> Rep SAM_V1_6_Read_Group_Run_Date x
from :: forall x.
SAM_V1_6_Read_Group_Run_Date -> Rep SAM_V1_6_Read_Group_Run_Date x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Run_Date x -> SAM_V1_6_Read_Group_Run_Date
to :: forall x.
Rep SAM_V1_6_Read_Group_Run_Date x -> SAM_V1_6_Read_Group_Run_Date
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Run_Date where
  SAM_V1_6_Read_Group_Run_Date ByteString
sam_v1_6_read_group_run_date_value1 == :: SAM_V1_6_Read_Group_Run_Date
-> SAM_V1_6_Read_Group_Run_Date -> Bool
== SAM_V1_6_Read_Group_Run_Date ByteString
sam_v1_6_read_group_run_date_value2 = ByteString
sam_v1_6_read_group_run_date_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_run_date_value2

instance Show SAM_V1_6_Read_Group_Run_Date where
  show :: SAM_V1_6_Read_Group_Run_Date -> String
show (SAM_V1_6_Read_Group_Run_Date ByteString
value) =
    String
"SAM_V1_6_Read_Group_Run_Date { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_run_date_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                            String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | FO tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Flow_Order = SAM_V1_6_Read_Group_Flow_Order { SAM_V1_6_Read_Group_Flow_Order -> ByteString
sam_v1_6_read_group_flow_order_value :: ByteString
                                                                        }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Flow_Order
 -> Rep SAM_V1_6_Read_Group_Flow_Order x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Flow_Order x
    -> SAM_V1_6_Read_Group_Flow_Order)
-> Generic SAM_V1_6_Read_Group_Flow_Order
forall x.
Rep SAM_V1_6_Read_Group_Flow_Order x
-> SAM_V1_6_Read_Group_Flow_Order
forall x.
SAM_V1_6_Read_Group_Flow_Order
-> Rep SAM_V1_6_Read_Group_Flow_Order x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Flow_Order
-> Rep SAM_V1_6_Read_Group_Flow_Order x
from :: forall x.
SAM_V1_6_Read_Group_Flow_Order
-> Rep SAM_V1_6_Read_Group_Flow_Order x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Flow_Order x
-> SAM_V1_6_Read_Group_Flow_Order
to :: forall x.
Rep SAM_V1_6_Read_Group_Flow_Order x
-> SAM_V1_6_Read_Group_Flow_Order
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Flow_Order where
  SAM_V1_6_Read_Group_Flow_Order ByteString
sam_v1_6_one_line_comment_value1 == :: SAM_V1_6_Read_Group_Flow_Order
-> SAM_V1_6_Read_Group_Flow_Order -> Bool
== SAM_V1_6_Read_Group_Flow_Order ByteString
sam_v1_6_read_group_flow_order_value2 = ByteString
sam_v1_6_one_line_comment_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_flow_order_value2

instance Show SAM_V1_6_Read_Group_Flow_Order where
  show :: SAM_V1_6_Read_Group_Flow_Order -> String
show (SAM_V1_6_Read_Group_Flow_Order ByteString
value) =
    String
"SAM_V1_6_Read_Group_Flow_Order { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_flow_order_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                              String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | KS tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Key_Sequence = SAM_V1_6_Read_Group_Key_Sequence { SAM_V1_6_Read_Group_Key_Sequence -> ByteString
sam_v1_6_read_group_key_sequence_value :: ByteString
                                                                            }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Key_Sequence
 -> Rep SAM_V1_6_Read_Group_Key_Sequence x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Key_Sequence x
    -> SAM_V1_6_Read_Group_Key_Sequence)
-> Generic SAM_V1_6_Read_Group_Key_Sequence
forall x.
Rep SAM_V1_6_Read_Group_Key_Sequence x
-> SAM_V1_6_Read_Group_Key_Sequence
forall x.
SAM_V1_6_Read_Group_Key_Sequence
-> Rep SAM_V1_6_Read_Group_Key_Sequence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Key_Sequence
-> Rep SAM_V1_6_Read_Group_Key_Sequence x
from :: forall x.
SAM_V1_6_Read_Group_Key_Sequence
-> Rep SAM_V1_6_Read_Group_Key_Sequence x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Key_Sequence x
-> SAM_V1_6_Read_Group_Key_Sequence
to :: forall x.
Rep SAM_V1_6_Read_Group_Key_Sequence x
-> SAM_V1_6_Read_Group_Key_Sequence
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Key_Sequence where
  SAM_V1_6_Read_Group_Key_Sequence ByteString
sam_v1_6_read_group_key_sequence_value1 == :: SAM_V1_6_Read_Group_Key_Sequence
-> SAM_V1_6_Read_Group_Key_Sequence -> Bool
== SAM_V1_6_Read_Group_Key_Sequence ByteString
sam_v1_6_read_group_key_sequence_value2 = ByteString
sam_v1_6_read_group_key_sequence_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_key_sequence_value2

instance Show SAM_V1_6_Read_Group_Key_Sequence where
  show :: SAM_V1_6_Read_Group_Key_Sequence -> String
show (SAM_V1_6_Read_Group_Key_Sequence ByteString
value) =
    String
"SAM_V1_6_Read_Group_Key_Sequence { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_key_sequence_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | LB tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Library = SAM_V1_6_Read_Group_Library { SAM_V1_6_Read_Group_Library -> ByteString
sam_v1_6_read_group_library_value :: ByteString
                                                                  }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Library -> Rep SAM_V1_6_Read_Group_Library x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Library x -> SAM_V1_6_Read_Group_Library)
-> Generic SAM_V1_6_Read_Group_Library
forall x.
Rep SAM_V1_6_Read_Group_Library x -> SAM_V1_6_Read_Group_Library
forall x.
SAM_V1_6_Read_Group_Library -> Rep SAM_V1_6_Read_Group_Library x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Library -> Rep SAM_V1_6_Read_Group_Library x
from :: forall x.
SAM_V1_6_Read_Group_Library -> Rep SAM_V1_6_Read_Group_Library x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Library x -> SAM_V1_6_Read_Group_Library
to :: forall x.
Rep SAM_V1_6_Read_Group_Library x -> SAM_V1_6_Read_Group_Library
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Library where
  SAM_V1_6_Read_Group_Library ByteString
sam_v1_6_read_group_library_value1 == :: SAM_V1_6_Read_Group_Library -> SAM_V1_6_Read_Group_Library -> Bool
== SAM_V1_6_Read_Group_Library ByteString
sam_v1_6_read_group_library_value2 = ByteString
sam_v1_6_read_group_library_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_library_value2

instance Show SAM_V1_6_Read_Group_Library where
  show :: SAM_V1_6_Read_Group_Library -> String
show (SAM_V1_6_Read_Group_Library ByteString
value) =
    String
"SAM_V1_6_Read_Group_Library { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_library_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | PG tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Programs = SAM_V1_6_Read_Group_Programs { SAM_V1_6_Read_Group_Programs -> ByteString
sam_v1_6_read_group_programs_value :: ByteString
                                                                    }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Programs -> Rep SAM_V1_6_Read_Group_Programs x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Programs x -> SAM_V1_6_Read_Group_Programs)
-> Generic SAM_V1_6_Read_Group_Programs
forall x.
Rep SAM_V1_6_Read_Group_Programs x -> SAM_V1_6_Read_Group_Programs
forall x.
SAM_V1_6_Read_Group_Programs -> Rep SAM_V1_6_Read_Group_Programs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Programs -> Rep SAM_V1_6_Read_Group_Programs x
from :: forall x.
SAM_V1_6_Read_Group_Programs -> Rep SAM_V1_6_Read_Group_Programs x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Programs x -> SAM_V1_6_Read_Group_Programs
to :: forall x.
Rep SAM_V1_6_Read_Group_Programs x -> SAM_V1_6_Read_Group_Programs
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Programs where
  SAM_V1_6_Read_Group_Programs ByteString
sam_v1_6_read_group_programs_value1 == :: SAM_V1_6_Read_Group_Programs
-> SAM_V1_6_Read_Group_Programs -> Bool
== SAM_V1_6_Read_Group_Programs ByteString
sam_v1_6_read_group_programs_value2 = ByteString
sam_v1_6_read_group_programs_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_programs_value2

instance Show SAM_V1_6_Read_Group_Programs where
  show :: SAM_V1_6_Read_Group_Programs -> String
show (SAM_V1_6_Read_Group_Programs ByteString
value) =
    String
"SAM_V1_6_Read_Group_Programs { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_programs_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                            String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | PI tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Predicted_Median_Insert_Size = SAM_V1_6_Read_Group_Predicted_Median_Insert_Size { SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> ByteString
sam_v1_6_read_group_predicted_median_insert_size_value :: ByteString
                                                                                                            }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
 -> Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
    -> SAM_V1_6_Read_Group_Predicted_Median_Insert_Size)
-> Generic SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
forall x.
Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
-> SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
forall x.
SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
-> Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
-> Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
from :: forall x.
SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
-> Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
-> SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
to :: forall x.
Rep SAM_V1_6_Read_Group_Predicted_Median_Insert_Size x
-> SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Predicted_Median_Insert_Size where
  SAM_V1_6_Read_Group_Predicted_Median_Insert_Size ByteString
sam_v1_6_read_group_predicted_median_insert_size_value1 == :: SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
-> SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> Bool
== SAM_V1_6_Read_Group_Predicted_Median_Insert_Size ByteString
sam_v1_6_read_group_predicted_median_insert_size_value2 = ByteString
sam_v1_6_read_group_predicted_median_insert_size_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_predicted_median_insert_size_value2

instance Show SAM_V1_6_Read_Group_Predicted_Median_Insert_Size where
  show :: SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> String
show (SAM_V1_6_Read_Group_Predicted_Median_Insert_Size ByteString
value) =
    String
"SAM_V1_6_Read_Group_Predicted_Median_Insert_Size { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_predicted_median_insert_size_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                                String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | PL tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Platform = SAM_V1_6_Read_Group_Platform { SAM_V1_6_Read_Group_Platform -> ByteString
sam_v1_6_read_group_platform_value :: ByteString
                                                                    }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Platform -> Rep SAM_V1_6_Read_Group_Platform x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Platform x -> SAM_V1_6_Read_Group_Platform)
-> Generic SAM_V1_6_Read_Group_Platform
forall x.
Rep SAM_V1_6_Read_Group_Platform x -> SAM_V1_6_Read_Group_Platform
forall x.
SAM_V1_6_Read_Group_Platform -> Rep SAM_V1_6_Read_Group_Platform x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Platform -> Rep SAM_V1_6_Read_Group_Platform x
from :: forall x.
SAM_V1_6_Read_Group_Platform -> Rep SAM_V1_6_Read_Group_Platform x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Platform x -> SAM_V1_6_Read_Group_Platform
to :: forall x.
Rep SAM_V1_6_Read_Group_Platform x -> SAM_V1_6_Read_Group_Platform
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Platform where
  SAM_V1_6_Read_Group_Platform ByteString
sam_v1_6_read_group_platform_value1 == :: SAM_V1_6_Read_Group_Platform
-> SAM_V1_6_Read_Group_Platform -> Bool
== SAM_V1_6_Read_Group_Platform ByteString
sam_v1_6_read_group_platform_value2 = ByteString
sam_v1_6_read_group_platform_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_platform_value2

instance Show SAM_V1_6_Read_Group_Platform where
  show :: SAM_V1_6_Read_Group_Platform -> String
show (SAM_V1_6_Read_Group_Platform ByteString
value) =
    String
"SAM_V1_6_Read_Group_Platform { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_platform_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                            String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | PM tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Platform_Model = SAM_V1_6_Read_Group_Platform_Model { SAM_V1_6_Read_Group_Platform_Model -> ByteString
sam_v1_6_read_group_platform_model_value :: ByteString
                                                                                }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Platform_Model
 -> Rep SAM_V1_6_Read_Group_Platform_Model x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Platform_Model x
    -> SAM_V1_6_Read_Group_Platform_Model)
-> Generic SAM_V1_6_Read_Group_Platform_Model
forall x.
Rep SAM_V1_6_Read_Group_Platform_Model x
-> SAM_V1_6_Read_Group_Platform_Model
forall x.
SAM_V1_6_Read_Group_Platform_Model
-> Rep SAM_V1_6_Read_Group_Platform_Model x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Platform_Model
-> Rep SAM_V1_6_Read_Group_Platform_Model x
from :: forall x.
SAM_V1_6_Read_Group_Platform_Model
-> Rep SAM_V1_6_Read_Group_Platform_Model x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Platform_Model x
-> SAM_V1_6_Read_Group_Platform_Model
to :: forall x.
Rep SAM_V1_6_Read_Group_Platform_Model x
-> SAM_V1_6_Read_Group_Platform_Model
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Platform_Model where
  SAM_V1_6_Read_Group_Platform_Model ByteString
sam_v1_6_read_group_platform_model_value1 == :: SAM_V1_6_Read_Group_Platform_Model
-> SAM_V1_6_Read_Group_Platform_Model -> Bool
== SAM_V1_6_Read_Group_Platform_Model ByteString
sam_v1_6_read_group_platform_model_value2 = ByteString
sam_v1_6_read_group_platform_model_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_platform_model_value2

instance Show SAM_V1_6_Read_Group_Platform_Model where
  show :: SAM_V1_6_Read_Group_Platform_Model -> String
show (SAM_V1_6_Read_Group_Platform_Model ByteString
value) =
    String
"SAM_V1_6_Read_Group_Platform_Model { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_platform_model_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                  String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | PU tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Platform_Unit = SAM_V1_6_Read_Group_Platform_Unit { SAM_V1_6_Read_Group_Platform_Unit -> ByteString
sam_v1_6_read_group_platform_unit_value :: ByteString
                                                                              }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Platform_Unit
 -> Rep SAM_V1_6_Read_Group_Platform_Unit x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Platform_Unit x
    -> SAM_V1_6_Read_Group_Platform_Unit)
-> Generic SAM_V1_6_Read_Group_Platform_Unit
forall x.
Rep SAM_V1_6_Read_Group_Platform_Unit x
-> SAM_V1_6_Read_Group_Platform_Unit
forall x.
SAM_V1_6_Read_Group_Platform_Unit
-> Rep SAM_V1_6_Read_Group_Platform_Unit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Platform_Unit
-> Rep SAM_V1_6_Read_Group_Platform_Unit x
from :: forall x.
SAM_V1_6_Read_Group_Platform_Unit
-> Rep SAM_V1_6_Read_Group_Platform_Unit x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Platform_Unit x
-> SAM_V1_6_Read_Group_Platform_Unit
to :: forall x.
Rep SAM_V1_6_Read_Group_Platform_Unit x
-> SAM_V1_6_Read_Group_Platform_Unit
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Platform_Unit where
  SAM_V1_6_Read_Group_Platform_Unit ByteString
sam_v1_6_read_group_platform_unit_value1 == :: SAM_V1_6_Read_Group_Platform_Unit
-> SAM_V1_6_Read_Group_Platform_Unit -> Bool
== SAM_V1_6_Read_Group_Platform_Unit ByteString
sam_v1_6_read_group_platform_unit_value2 = ByteString
sam_v1_6_read_group_platform_unit_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_platform_unit_value2

instance Show SAM_V1_6_Read_Group_Platform_Unit where
  show :: SAM_V1_6_Read_Group_Platform_Unit -> String
show (SAM_V1_6_Read_Group_Platform_Unit ByteString
value) =
    String
"SAM_V1_6_Read_Group_Platform_Unit { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_platform_unit_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                                 String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"

-- | SM tag for @"SAM_V1_6_Read_Group"@.
newtype SAM_V1_6_Read_Group_Sample = SAM_V1_6_Read_Group_Sample { SAM_V1_6_Read_Group_Sample -> ByteString
sam_v1_6_read_group_sample_value :: ByteString
                                                                }
  deriving ((forall x.
 SAM_V1_6_Read_Group_Sample -> Rep SAM_V1_6_Read_Group_Sample x)
-> (forall x.
    Rep SAM_V1_6_Read_Group_Sample x -> SAM_V1_6_Read_Group_Sample)
-> Generic SAM_V1_6_Read_Group_Sample
forall x.
Rep SAM_V1_6_Read_Group_Sample x -> SAM_V1_6_Read_Group_Sample
forall x.
SAM_V1_6_Read_Group_Sample -> Rep SAM_V1_6_Read_Group_Sample x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Read_Group_Sample -> Rep SAM_V1_6_Read_Group_Sample x
from :: forall x.
SAM_V1_6_Read_Group_Sample -> Rep SAM_V1_6_Read_Group_Sample x
$cto :: forall x.
Rep SAM_V1_6_Read_Group_Sample x -> SAM_V1_6_Read_Group_Sample
to :: forall x.
Rep SAM_V1_6_Read_Group_Sample x -> SAM_V1_6_Read_Group_Sample
Generic,Typeable)

instance Eq SAM_V1_6_Read_Group_Sample where
  SAM_V1_6_Read_Group_Sample ByteString
sam_v1_6_read_group_sample_value1 == :: SAM_V1_6_Read_Group_Sample -> SAM_V1_6_Read_Group_Sample -> Bool
== SAM_V1_6_Read_Group_Sample ByteString
sam_v1_6_read_group_sample_value2 = ByteString
sam_v1_6_read_group_sample_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_read_group_sample_value2

instance Show SAM_V1_6_Read_Group_Sample where
  show :: SAM_V1_6_Read_Group_Sample -> String
show (SAM_V1_6_Read_Group_Sample ByteString
value) =
    String
"SAM_V1_6_Read_Group_Sample { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_read_group_sample_value = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (ByteString -> String
forall a. Show a => a -> String
show ByteString
value)                          String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"