{-# 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.RG -- 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.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.Sequence import Data.Word -- | 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_identifer :: SAM_V1_6_Read_Group_Identifier , sam_v1_6_read_group_barcode_sequence :: Maybe SAM_V1_6_Read_Group_Barcode_Sequence , sam_v1_6_read_group_sequencing_center :: Maybe SAM_V1_6_Read_Group_Sequencing_Center , sam_v1_6_read_group_description :: Maybe SAM_V1_6_Read_Group_Description , sam_v1_6_read_group_run_date :: Maybe SAM_V1_6_Read_Group_Run_Date , sam_v1_6_read_group_flow_order :: Maybe SAM_V1_6_Read_Group_Flow_Order , sam_v1_6_read_group_key_sequence :: Maybe SAM_V1_6_Read_Group_Key_Sequence , sam_v1_6_read_group_library :: Maybe SAM_V1_6_Read_Group_Library , sam_v1_6_read_group_programs :: Maybe SAM_V1_6_Read_Group_Programs , sam_v1_6_read_group_predicted_median_insert_size :: Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size , sam_v1_6_read_group_platform :: Maybe SAM_V1_6_Read_Group_Platform , sam_v1_6_read_group_platform_model :: Maybe SAM_V1_6_Read_Group_Platform_Model , sam_v1_6_read_group_platform_unit :: Maybe SAM_V1_6_Read_Group_Platform_Unit , sam_v1_6_read_group_sample :: Maybe SAM_V1_6_Read_Group_Sample } -- | ID tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Identifier = SAM_V1_6_Read_Group_Identifier { sam_v1_6_read_group_identifer_tag :: Seq Word8 , sam_v1_6_read_group_identifer_value :: ByteString } -- | BC tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Barcode_Sequence = SAM_V1_6_Read_Group_Barcode_Sequence { sam_v1_6_read_group_barcode_sequence_tag :: Seq Word8 , sam_v1_6_read_group_barcode_sequence_value :: ByteString } -- | CN tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Sequencing_Center = SAM_V1_6_Read_Group_Sequencing_Center { sam_v1_6_read_group_sequencing_center_tag :: Seq Word8 , sam_v1_6_read_group_sequencing_center_value :: ByteString } -- | DS tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Description = SAM_V1_6_Read_Group_Description { sam_v1_6_read_group_description_tag :: Seq Word8 , sam_v1_6_read_group_description_value :: ByteString } -- | DT tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Run_Date = SAM_V1_6_Read_Group_Run_Date { sam_v1_6_read_group_run_date_tag :: Seq Word8 , sam_v1_6_read_group_run_date_value :: ByteString } -- | FO tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Flow_Order = SAM_V1_6_Read_Group_Flow_Order { sam_v1_6_read_group_flow_order_tag :: Seq Word8 , sam_v1_6_read_group_flow_order_value :: ByteString } -- | KS tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Key_Sequence = SAM_V1_6_Read_Group_Key_Sequence { sam_v1_6_read_group_key_sequence_tag :: Seq Word8 , sam_v1_6_read_group_key_sequence_value :: ByteString } -- | LB tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Library = SAM_V1_6_Read_Group_Library { sam_v1_6_read_group_library_tag :: Seq Word8 , sam_v1_6_read_group_library_value :: ByteString } -- | PG tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Programs = SAM_V1_6_Read_Group_Programs { sam_v1_6_read_group_programs_tag :: Seq Word8 , sam_v1_6_read_group_programs_value :: ByteString } -- | PI tag for @"SAM_V1_6_Read_Group"@. data 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_tag :: Seq Word8 , sam_v1_6_read_group_predicted_median_insert_size_value :: ByteString } -- | PL tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Platform = SAM_V1_6_Read_Group_Platform { sam_v1_6_read_group_platform_tag :: Seq Word8 , sam_v1_6_read_group_platform_value :: ByteString } -- | PM tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Platform_Model = SAM_V1_6_Read_Group_Platform_Model { sam_v1_6_read_group_platform_model_tag :: Seq Word8 , sam_v1_6_read_group_platform_model_value :: ByteString } -- | PU tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Platform_Unit = SAM_V1_6_Read_Group_Platform_Unit { sam_v1_6_read_group_platform_unit_tag :: Seq Word8 , sam_v1_6_read_group_platform_unit_value :: ByteString } -- | SM tag for @"SAM_V1_6_Read_Group"@. data SAM_V1_6_Read_Group_Sample = SAM_V1_6_Read_Group_Sample { sam_v1_6_read_group_sample_tag :: Seq Word8 , sam_v1_6_read_group_sample_value :: ByteString }