{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists       #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE PackageImports        #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE TemplateHaskell       #-}
{-# LANGUAGE TypeFamilies          #-}
{-# Language QuasiQuotes           #-}

-- |
-- Module      :  Data.SAM.Version1_6.Header.SQ
-- 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.Header.SQ ( -- * SAM version 1.6 Reference sequence dictionary data type
                                       SAM_V1_6_Reference_Sequence_Dictionary(..),
                                       -- * SAM version 1.6 Reference sequence dictionary data types
                                       SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Description(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Species(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology(..),
                                       SAM_V1_6_Reference_Sequence_Dictionary_URI(..)
                                     ) where

import Data.ByteString
import Data.Sequence
import Data.Word


-- | Custom SAM (version 1.6) @"SAM_V1_6_Reference_Sequence_Dictionary"@ 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_Reference_Sequence_Dictionary = SAM_V1_6_Reference_Sequence_Dictionary { SAM_V1_6_Reference_Sequence_Dictionary
-> SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name
sam_v1_6_reference_sequence_dictionary_reference_sequence_name                        :: SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length
sam_v1_6_reference_sequence_dictionary_reference_sequence_length                      :: SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus
sam_v1_6_reference_sequence_dictionary_reference_alternative_locus                    :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe
     SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names
sam_v1_6_reference_sequence_dictionary_reference_alternative_reference_sequence_names :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe
     SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier
sam_v1_6_reference_sequence_dictionary_genome_assembly_identifier                     :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_Description
sam_v1_6_reference_sequence_dictionary_description                                    :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Description
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum
sam_v1_6_reference_sequence_dictionary_md5_checksum                                   :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_Species
sam_v1_6_reference_sequence_dictionary_species                                        :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Species
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology
sam_v1_6_reference_sequence_dictionary_molecule_topology                              :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology                                       
                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary
-> Maybe SAM_V1_6_Reference_Sequence_Dictionary_URI
sam_v1_6_reference_sequence_dictionary_uri                                            :: Maybe SAM_V1_6_Reference_Sequence_Dictionary_URI 
                                                                                     }

-- | SN tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name = SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name { SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_reference_sequence_name_tag   :: Seq Word8
                                                                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Name
-> ByteString
sam_v1_6_reference_sequence_dictionary_reference_sequence_name_value :: ByteString 
                         }

-- | LN tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length = SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length { SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_reference_sequence_length_tag   :: Seq Word8
                                                                                                                                         , SAM_V1_6_Reference_Sequence_Dictionary_Reference_Sequence_Length
-> ByteString
sam_v1_6_reference_sequence_dictionary_reference_sequence_length_value :: ByteString
                             }

-- | AH tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus = SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus { SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_reference_alternative_locus_tag   :: Seq Word8
                                                                                                                         , SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Locus
-> ByteString
sam_v1_6_reference_sequence_dictionary_reference_alternative_locus_value :: ByteString
             }

-- | AN tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names = SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names { SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_reference_alternative_reference_sequence_names_tag   :: Seq Word8
                                                                                                                                                               , SAM_V1_6_Reference_Sequence_Dictionary_Alternative_Reference_Sequence_Names
-> ByteString
sam_v1_6_reference_sequence_dictionary_reference_alternative_reference_sequence_names_value :: ByteString
                                                                                                                                                               }

-- | AS tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier = SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier { SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_genome_assembly_identifier_tag   :: Seq Word8
                                                                                                                                           , SAM_V1_6_Reference_Sequence_Dictionary_Genome_Assembly_Identifier
-> ByteString
sam_v1_6_reference_sequence_dictionary_genome_assembly_identifier_value :: ByteString
                                                                                                                                           }

-- | DS tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Description = SAM_V1_6_Reference_Sequence_Dictionary_Description { SAM_V1_6_Reference_Sequence_Dictionary_Description -> Seq Word8
sam_v1_6_reference_sequence_dictionary_description_tag   :: Seq Word8
                                                                                                             , SAM_V1_6_Reference_Sequence_Dictionary_Description -> ByteString
sam_v1_6_reference_sequence_dictionary_description_value :: ByteString
                                                                                                             }

-- | M5 tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum = SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum { SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum -> Seq Word8
sam_v1_6_reference_sequence_dictionary_md5_checksum_tag   :: Seq Word8
                                                                                                               , SAM_V1_6_Reference_Sequence_Dictionary_MD5_Checksum -> ByteString
sam_v1_6_reference_sequence_dictionary_md5_checksum_value :: ByteString
                                                                                                               }

-- | SP tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Species = SAM_V1_6_Reference_Sequence_Dictionary_Species { SAM_V1_6_Reference_Sequence_Dictionary_Species -> Seq Word8
sam_v1_6_reference_sequence_dictionary_species_tag   :: Seq Word8
                                                                                                     , SAM_V1_6_Reference_Sequence_Dictionary_Species -> ByteString
sam_v1_6_reference_sequence_dictionary_species_value :: ByteString
                                                                                                     }

-- | TP tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology = SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology { SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology
-> Seq Word8
sam_v1_6_reference_sequence_dictionary_molecule_topology_tag   :: Seq Word8
                                                                                                                         , SAM_V1_6_Reference_Sequence_Dictionary_Molecule_Topology
-> ByteString
sam_v1_6_reference_sequence_dictionary_molecule_topology_value :: ByteString
                                                                                                                         }

-- | UR tag for @"SAM_V1_6_Reference_Sequence_Dictionary"@.
data SAM_V1_6_Reference_Sequence_Dictionary_URI = SAM_V1_6_Reference_Sequence_Dictionary_URI { SAM_V1_6_Reference_Sequence_Dictionary_URI -> Seq Word8
sam_v1_6_reference_sequence_dictionary_uri_tag   :: Seq Word8
                                                                                             , SAM_V1_6_Reference_Sequence_Dictionary_URI -> ByteString
sam_v1_6_reference_sequence_dictionary_uri_value :: ByteString
                                                                                             }