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

-- |
-- Module      :  Data.SAM.Version1_6.Base
-- 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.Base ( -- * SAM version 1.6 data type
                                  SAM_V1_6(..)
                                ) where

import Data.SAM.Version1_6.Alignment
import Data.SAM.Version1_6.Header

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

-- | Custom @"SAM_V1_6"@ (SAM version 1.6) data type.
--
-- See the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
data SAM_V1_6 = SAM_V1_6 { SAM_V1_6 -> Maybe SAM_V1_6_File_Level_Metadata
sam_v1_6_file_level_metadata           :: Maybe SAM_V1_6_File_Level_Metadata                 -- ^ File-level metadata.
                                                                                                                        -- Optional. If present,
                                                                                                                        -- there must be only one
                                                                                                                        -- @HD line and it must be
                                                                                                                        -- the first line of the file. 
                         , SAM_V1_6 -> Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
sam_v1_6_reference_sequence_dictionary :: Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary) -- ^ Reference sequence dictionary.
                                                                                                                        -- The order of @SQ lines defines the
                                                                                                                        -- alignment sorting order.
                         , SAM_V1_6 -> Maybe (Seq SAM_V1_6_Read_Group)
sam_v1_6_read_group                    :: Maybe (Seq SAM_V1_6_Read_Group)                    -- ^ Read group.
                                                                                                                        -- Unordered multiple @RG
                                                                                                                        -- lines are allowed.
                         , SAM_V1_6 -> Maybe SAM_V1_6_Program
sam_v1_6_program                       :: Maybe SAM_V1_6_Program                             -- ^ Program.
                         , SAM_V1_6 -> Maybe (Seq SAM_V1_6_One_Line_Comment)
sam_v1_6_one_line_comment              :: Maybe (Seq SAM_V1_6_One_Line_Comment)              -- ^ One-line text comment.
                                                                                                                        -- Unordered multiple @CO lines
                                                                                                                        -- are allowed. UTF-8 encoding
                                                                                                                        -- may be used.
                         , SAM_V1_6 -> Seq SAM_V1_6_Alignment
sam_v1_6_alignment                     :: Seq SAM_V1_6_Alignment                             -- ^ The alignment section (mandatory
                                                                                                                        -- and optional fields).
                         }
  deriving ((forall x. SAM_V1_6 -> Rep SAM_V1_6 x)
-> (forall x. Rep SAM_V1_6 x -> SAM_V1_6) -> Generic SAM_V1_6
forall x. Rep SAM_V1_6 x -> SAM_V1_6
forall x. SAM_V1_6 -> Rep SAM_V1_6 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SAM_V1_6 -> Rep SAM_V1_6 x
from :: forall x. SAM_V1_6 -> Rep SAM_V1_6 x
$cto :: forall x. Rep SAM_V1_6 x -> SAM_V1_6
to :: forall x. Rep SAM_V1_6 x -> SAM_V1_6
Generic,Typeable)

instance Eq SAM_V1_6 where
  SAM_V1_6 Maybe SAM_V1_6_File_Level_Metadata
sam_v1_6_file_level_metadata1
           Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
sam_v1_6_reference_sequence_dictionary1
           Maybe (Seq SAM_V1_6_Read_Group)
sam_v1_6_read_group1
           Maybe SAM_V1_6_Program
sam_v1_6_program1
           Maybe (Seq SAM_V1_6_One_Line_Comment)
sam_v1_6_one_line_comment1
           Seq SAM_V1_6_Alignment
sam_v1_6_alignment1 == :: SAM_V1_6 -> SAM_V1_6 -> Bool
== SAM_V1_6 Maybe SAM_V1_6_File_Level_Metadata
sam_v1_6_file_level_metadata2
                                           Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
sam_v1_6_reference_sequence_dictionary2
                                           Maybe (Seq SAM_V1_6_Read_Group)
sam_v1_6_read_group2
                                           Maybe SAM_V1_6_Program
sam_v1_6_program2
                                           Maybe (Seq SAM_V1_6_One_Line_Comment)
sam_v1_6_one_line_comment2
                                           Seq SAM_V1_6_Alignment
sam_v1_6_alignment2 = Maybe SAM_V1_6_File_Level_Metadata
sam_v1_6_file_level_metadata1           Maybe SAM_V1_6_File_Level_Metadata
-> Maybe SAM_V1_6_File_Level_Metadata -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_File_Level_Metadata
sam_v1_6_file_level_metadata2           Bool -> Bool -> Bool
&&
                                                                 Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
sam_v1_6_reference_sequence_dictionary1 Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
-> Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
sam_v1_6_reference_sequence_dictionary2 Bool -> Bool -> Bool
&&
                                                                 Maybe (Seq SAM_V1_6_Read_Group)
sam_v1_6_read_group1                    Maybe (Seq SAM_V1_6_Read_Group)
-> Maybe (Seq SAM_V1_6_Read_Group) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Seq SAM_V1_6_Read_Group)
sam_v1_6_read_group2                    Bool -> Bool -> Bool
&&
                                                                 Maybe SAM_V1_6_Program
sam_v1_6_program1                       Maybe SAM_V1_6_Program -> Maybe SAM_V1_6_Program -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe SAM_V1_6_Program
sam_v1_6_program2                       Bool -> Bool -> Bool
&&
                                                                 Maybe (Seq SAM_V1_6_One_Line_Comment)
sam_v1_6_one_line_comment1              Maybe (Seq SAM_V1_6_One_Line_Comment)
-> Maybe (Seq SAM_V1_6_One_Line_Comment) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Seq SAM_V1_6_One_Line_Comment)
sam_v1_6_one_line_comment2              Bool -> Bool -> Bool
&&
                                                                 Seq SAM_V1_6_Alignment
sam_v1_6_alignment1                     Seq SAM_V1_6_Alignment -> Seq SAM_V1_6_Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Seq SAM_V1_6_Alignment
sam_v1_6_alignment2

instance Show SAM_V1_6 where
  show :: SAM_V1_6 -> String
show (SAM_V1_6 Maybe SAM_V1_6_File_Level_Metadata
file_level_metadata
                 Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
reference_sequence_dictionary
                 Maybe (Seq SAM_V1_6_Read_Group)
read_group Maybe SAM_V1_6_Program
program
                 Maybe (Seq SAM_V1_6_One_Line_Comment)
one_line_comment
                 Seq SAM_V1_6_Alignment
alignment
       ) =
    String
"SAM_V1_6 { "                                  String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
"sam_v1_6_file_level_metadata = "              String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_File_Level_Metadata -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_File_Level_Metadata
file_level_metadata)                     String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_reference_sequence_dictionary = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary) -> String
forall a. Show a => a -> String
show Maybe (Seq SAM_V1_6_Reference_Sequence_Dictionary)
reference_sequence_dictionary)           String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_read_group = "                    String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe (Seq SAM_V1_6_Read_Group) -> String
forall a. Show a => a -> String
show Maybe (Seq SAM_V1_6_Read_Group)
read_group)                              String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_program = "                       String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe SAM_V1_6_Program -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program
program)                                 String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_one_line_comment = "              String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Maybe (Seq SAM_V1_6_One_Line_Comment) -> String
forall a. Show a => a -> String
show Maybe (Seq SAM_V1_6_One_Line_Comment)
one_line_comment)                        String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" , sam_v1_6_alignment = "                     String -> ShowS
forall a. [a] -> [a] -> [a]
++
    (Seq SAM_V1_6_Alignment -> String
forall a. Show a => a -> String
show Seq SAM_V1_6_Alignment
alignment)                               String -> ShowS
forall a. [a] -> [a] -> [a]
++
    String
" }"