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

-- |
-- Module      :  Data.SAM.Version1_6.Alignment.AOPT
-- Copyright   :  (c) Matthew Mosior 2023
-- License     :  BSD-style
-- Maintainer  :  mattm.github@gmail.com
-- Portability :  portable
--
-- = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this library are expected to track development
-- closely.
--
-- All credit goes to the author(s)/maintainer(s) of the
-- [containers](https://hackage.haskell.org/package/containers) library
-- for the above warning text.
--
-- = Description
--
-- This library enables the decoding/encoding of SAM, BAM and CRAM file formats.

module Data.SAM.Version1_6.Alignment.AOPT ( -- * SAM version 1.6 alignment optional fields data type
                                            SAM_V1_6_Alignment_AOPT(..)
                                          ) where

import Data.ByteString (ByteString)
import Data.Data
import Generics.Deriving.Base


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

instance Eq SAM_V1_6_Alignment_AOPT where
  SAM_V1_6_Alignment_AOPT ByteString
sam_v1_6_alignment_aopt_tag1
                          ByteString
sam_v1_6_alignment_aopt_value1 == :: SAM_V1_6_Alignment_AOPT -> SAM_V1_6_Alignment_AOPT -> Bool
== SAM_V1_6_Alignment_AOPT ByteString
sam_v1_6_alignment_aopt_tag2
                                                                                    ByteString
sam_v1_6_alignment_aopt_value2 = ByteString
sam_v1_6_alignment_aopt_tag1   ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_alignment_aopt_tag2     Bool -> Bool -> Bool
&&
                                                                                                                     ByteString
sam_v1_6_alignment_aopt_value1  ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_alignment_aopt_value2

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