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

-- |
-- Module      :  Data.SAM.Version1_6.Header.CO
-- 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.CO ( -- * SAM version 1.6 One-line text comment data type
                                       SAM_V1_6_One_Line_Comment(..)
                                     ) where

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

-- | Custom SAM (version 1.6) @"SAM_V1_6_One_Line_Comment"@ data type.
--
-- See section 1.3 of the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
newtype SAM_V1_6_One_Line_Comment = SAM_V1_6_One_Line_Comment { SAM_V1_6_One_Line_Comment -> ByteString
sam_v1_6_one_line_comment_value :: ByteString
                                                              }
  deriving ((forall x.
 SAM_V1_6_One_Line_Comment -> Rep SAM_V1_6_One_Line_Comment x)
-> (forall x.
    Rep SAM_V1_6_One_Line_Comment x -> SAM_V1_6_One_Line_Comment)
-> Generic SAM_V1_6_One_Line_Comment
forall x.
Rep SAM_V1_6_One_Line_Comment x -> SAM_V1_6_One_Line_Comment
forall x.
SAM_V1_6_One_Line_Comment -> Rep SAM_V1_6_One_Line_Comment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_One_Line_Comment -> Rep SAM_V1_6_One_Line_Comment x
from :: forall x.
SAM_V1_6_One_Line_Comment -> Rep SAM_V1_6_One_Line_Comment x
$cto :: forall x.
Rep SAM_V1_6_One_Line_Comment x -> SAM_V1_6_One_Line_Comment
to :: forall x.
Rep SAM_V1_6_One_Line_Comment x -> SAM_V1_6_One_Line_Comment
Generic,Typeable)

instance Eq SAM_V1_6_One_Line_Comment where
  SAM_V1_6_One_Line_Comment ByteString
sam_v1_6_one_line_comment_value1 == :: SAM_V1_6_One_Line_Comment -> SAM_V1_6_One_Line_Comment -> Bool
== SAM_V1_6_One_Line_Comment ByteString
sam_v1_6_one_line_comment_value2 = ByteString
sam_v1_6_one_line_comment_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_one_line_comment_value2

instance Show SAM_V1_6_One_Line_Comment where
  show :: SAM_V1_6_One_Line_Comment -> String
show (SAM_V1_6_One_Line_Comment ByteString
value) = String
"SAM_V1_6_One_Line_Comment { "       String -> ShowS
forall a. [a] -> [a] -> [a]
++
                                           String
"sam_v1_6_one_line_comment_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
" }"