{-# 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 (
SAM_V1_6_Read_Group(..),
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
data SAM_V1_6_Read_Group = SAM_V1_6_Read_Group { SAM_V1_6_Read_Group -> SAM_V1_6_Read_Group_Identifier
sam_v1_6_read_group_identifer :: SAM_V1_6_Read_Group_Identifier
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Barcode_Sequence
sam_v1_6_read_group_barcode_sequence :: Maybe SAM_V1_6_Read_Group_Barcode_Sequence
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Sequencing_Center
sam_v1_6_read_group_sequencing_center :: Maybe SAM_V1_6_Read_Group_Sequencing_Center
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Description
sam_v1_6_read_group_description :: Maybe SAM_V1_6_Read_Group_Description
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Run_Date
sam_v1_6_read_group_run_date :: Maybe SAM_V1_6_Read_Group_Run_Date
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Flow_Order
sam_v1_6_read_group_flow_order :: Maybe SAM_V1_6_Read_Group_Flow_Order
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Key_Sequence
sam_v1_6_read_group_key_sequence :: Maybe SAM_V1_6_Read_Group_Key_Sequence
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Library
sam_v1_6_read_group_library :: Maybe SAM_V1_6_Read_Group_Library
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Programs
sam_v1_6_read_group_programs :: Maybe SAM_V1_6_Read_Group_Programs
, SAM_V1_6_Read_Group
-> Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
sam_v1_6_read_group_predicted_median_insert_size :: Maybe SAM_V1_6_Read_Group_Predicted_Median_Insert_Size
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform
sam_v1_6_read_group_platform :: Maybe SAM_V1_6_Read_Group_Platform
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform_Model
sam_v1_6_read_group_platform_model :: Maybe SAM_V1_6_Read_Group_Platform_Model
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Platform_Unit
sam_v1_6_read_group_platform_unit :: Maybe SAM_V1_6_Read_Group_Platform_Unit
, SAM_V1_6_Read_Group -> Maybe SAM_V1_6_Read_Group_Sample
sam_v1_6_read_group_sample :: Maybe SAM_V1_6_Read_Group_Sample
}
data SAM_V1_6_Read_Group_Identifier = SAM_V1_6_Read_Group_Identifier { SAM_V1_6_Read_Group_Identifier -> Seq Word8
sam_v1_6_read_group_identifer_tag :: Seq Word8
, SAM_V1_6_Read_Group_Identifier -> ByteString
sam_v1_6_read_group_identifer_value :: ByteString
}
data SAM_V1_6_Read_Group_Barcode_Sequence = SAM_V1_6_Read_Group_Barcode_Sequence { SAM_V1_6_Read_Group_Barcode_Sequence -> Seq Word8
sam_v1_6_read_group_barcode_sequence_tag :: Seq Word8
, SAM_V1_6_Read_Group_Barcode_Sequence -> ByteString
sam_v1_6_read_group_barcode_sequence_value :: ByteString
}
data SAM_V1_6_Read_Group_Sequencing_Center = SAM_V1_6_Read_Group_Sequencing_Center { SAM_V1_6_Read_Group_Sequencing_Center -> Seq Word8
sam_v1_6_read_group_sequencing_center_tag :: Seq Word8
, SAM_V1_6_Read_Group_Sequencing_Center -> ByteString
sam_v1_6_read_group_sequencing_center_value :: ByteString
}
data SAM_V1_6_Read_Group_Description = SAM_V1_6_Read_Group_Description { SAM_V1_6_Read_Group_Description -> Seq Word8
sam_v1_6_read_group_description_tag :: Seq Word8
, SAM_V1_6_Read_Group_Description -> ByteString
sam_v1_6_read_group_description_value :: ByteString
}
data SAM_V1_6_Read_Group_Run_Date = SAM_V1_6_Read_Group_Run_Date { SAM_V1_6_Read_Group_Run_Date -> Seq Word8
sam_v1_6_read_group_run_date_tag :: Seq Word8
, SAM_V1_6_Read_Group_Run_Date -> ByteString
sam_v1_6_read_group_run_date_value :: ByteString
}
data SAM_V1_6_Read_Group_Flow_Order = SAM_V1_6_Read_Group_Flow_Order { SAM_V1_6_Read_Group_Flow_Order -> Seq Word8
sam_v1_6_read_group_flow_order_tag :: Seq Word8
, SAM_V1_6_Read_Group_Flow_Order -> ByteString
sam_v1_6_read_group_flow_order_value :: ByteString
}
data SAM_V1_6_Read_Group_Key_Sequence = SAM_V1_6_Read_Group_Key_Sequence { SAM_V1_6_Read_Group_Key_Sequence -> Seq Word8
sam_v1_6_read_group_key_sequence_tag :: Seq Word8
, SAM_V1_6_Read_Group_Key_Sequence -> ByteString
sam_v1_6_read_group_key_sequence_value :: ByteString
}
data SAM_V1_6_Read_Group_Library = SAM_V1_6_Read_Group_Library { SAM_V1_6_Read_Group_Library -> Seq Word8
sam_v1_6_read_group_library_tag :: Seq Word8
, SAM_V1_6_Read_Group_Library -> ByteString
sam_v1_6_read_group_library_value :: ByteString
}
data SAM_V1_6_Read_Group_Programs = SAM_V1_6_Read_Group_Programs { SAM_V1_6_Read_Group_Programs -> Seq Word8
sam_v1_6_read_group_programs_tag :: Seq Word8
, SAM_V1_6_Read_Group_Programs -> ByteString
sam_v1_6_read_group_programs_value :: ByteString
}
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 -> Seq Word8
sam_v1_6_read_group_predicted_median_insert_size_tag :: Seq Word8
, SAM_V1_6_Read_Group_Predicted_Median_Insert_Size -> ByteString
sam_v1_6_read_group_predicted_median_insert_size_value :: ByteString
}
data SAM_V1_6_Read_Group_Platform = SAM_V1_6_Read_Group_Platform { SAM_V1_6_Read_Group_Platform -> Seq Word8
sam_v1_6_read_group_platform_tag :: Seq Word8
, SAM_V1_6_Read_Group_Platform -> ByteString
sam_v1_6_read_group_platform_value :: ByteString
}
data SAM_V1_6_Read_Group_Platform_Model = SAM_V1_6_Read_Group_Platform_Model { SAM_V1_6_Read_Group_Platform_Model -> Seq Word8
sam_v1_6_read_group_platform_model_tag :: Seq Word8
, SAM_V1_6_Read_Group_Platform_Model -> ByteString
sam_v1_6_read_group_platform_model_value :: ByteString
}
data SAM_V1_6_Read_Group_Platform_Unit = SAM_V1_6_Read_Group_Platform_Unit { SAM_V1_6_Read_Group_Platform_Unit -> Seq Word8
sam_v1_6_read_group_platform_unit_tag :: Seq Word8
, SAM_V1_6_Read_Group_Platform_Unit -> ByteString
sam_v1_6_read_group_platform_unit_value :: ByteString
}
data SAM_V1_6_Read_Group_Sample = SAM_V1_6_Read_Group_Sample { SAM_V1_6_Read_Group_Sample -> Seq Word8
sam_v1_6_read_group_sample_tag :: Seq Word8
, SAM_V1_6_Read_Group_Sample -> ByteString
sam_v1_6_read_group_sample_value :: ByteString
}