{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# 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.PG (
SAM_V1_6_Program(..),
SAM_V1_6_Program_Record_Identifier(..),
SAM_V1_6_Program_Name(..),
SAM_V1_6_Program_Command_Line(..),
SAM_V1_6_Program_Previous_PG_ID(..),
SAM_V1_6_Program_Description(..),
SAM_V1_6_Program_Version(..)
) where
import Data.ByteString
import Data.Data
import Data.Sequence
import Data.Word
import Generics.Deriving.Base
data SAM_V1_6_Program = SAM_V1_6_Program { SAM_V1_6_Program -> SAM_V1_6_Program_Record_Identifier
sam_v1_6_program_record_identifier :: SAM_V1_6_Program_Record_Identifier
, SAM_V1_6_Program -> Maybe SAM_V1_6_Program_Name
sam_v1_6_program_name :: Maybe SAM_V1_6_Program_Name
, SAM_V1_6_Program -> Maybe SAM_V1_6_Program_Command_Line
sam_v1_6_program_command_line :: Maybe SAM_V1_6_Program_Command_Line
, SAM_V1_6_Program -> Maybe SAM_V1_6_Program_Previous_PG_ID
sam_v1_6_program_previous_pg_id :: Maybe SAM_V1_6_Program_Previous_PG_ID
, SAM_V1_6_Program -> Maybe SAM_V1_6_Program_Description
sam_v1_6_program_description :: Maybe SAM_V1_6_Program_Description
, SAM_V1_6_Program -> Maybe SAM_V1_6_Program_Version
sam_v1_6_program_version :: Maybe SAM_V1_6_Program_Version
}
deriving ((forall x. SAM_V1_6_Program -> Rep SAM_V1_6_Program x)
-> (forall x. Rep SAM_V1_6_Program x -> SAM_V1_6_Program)
-> Generic SAM_V1_6_Program
forall x. Rep SAM_V1_6_Program x -> SAM_V1_6_Program
forall x. SAM_V1_6_Program -> Rep SAM_V1_6_Program x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SAM_V1_6_Program -> Rep SAM_V1_6_Program x
from :: forall x. SAM_V1_6_Program -> Rep SAM_V1_6_Program x
$cto :: forall x. Rep SAM_V1_6_Program x -> SAM_V1_6_Program
to :: forall x. Rep SAM_V1_6_Program x -> SAM_V1_6_Program
Generic,Typeable)
instance Show SAM_V1_6_Program where
show :: SAM_V1_6_Program -> String
show (SAM_V1_6_Program SAM_V1_6_Program_Record_Identifier
record_identifier Maybe SAM_V1_6_Program_Name
name Maybe SAM_V1_6_Program_Command_Line
command_line Maybe SAM_V1_6_Program_Previous_PG_ID
previous_pg_id Maybe SAM_V1_6_Program_Description
description Maybe SAM_V1_6_Program_Version
version) =
String
"SAM_V1_6_Program { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"record_identifier = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(SAM_V1_6_Program_Record_Identifier -> String
forall a. Show a => a -> String
show SAM_V1_6_Program_Record_Identifier
record_identifier) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , name = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe SAM_V1_6_Program_Name -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program_Name
name) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , command_line = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe SAM_V1_6_Program_Command_Line -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program_Command_Line
command_line) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , previous_pg_id = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe SAM_V1_6_Program_Previous_PG_ID -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program_Previous_PG_ID
previous_pg_id) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , description = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe SAM_V1_6_Program_Description -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program_Description
description) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , version = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe SAM_V1_6_Program_Version -> String
forall a. Show a => a -> String
show Maybe SAM_V1_6_Program_Version
version) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" }"
data SAM_V1_6_Program_Record_Identifier = SAM_V1_6_Program_Record_Identifier { SAM_V1_6_Program_Record_Identifier -> Seq Word8
sam_v1_6_program_record_identifier_tag :: Seq Word8
, SAM_V1_6_Program_Record_Identifier -> ByteString
sam_v1_6_program_record_identifier_value :: ByteString
}
deriving ((forall x.
SAM_V1_6_Program_Record_Identifier
-> Rep SAM_V1_6_Program_Record_Identifier x)
-> (forall x.
Rep SAM_V1_6_Program_Record_Identifier x
-> SAM_V1_6_Program_Record_Identifier)
-> Generic SAM_V1_6_Program_Record_Identifier
forall x.
Rep SAM_V1_6_Program_Record_Identifier x
-> SAM_V1_6_Program_Record_Identifier
forall x.
SAM_V1_6_Program_Record_Identifier
-> Rep SAM_V1_6_Program_Record_Identifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Program_Record_Identifier
-> Rep SAM_V1_6_Program_Record_Identifier x
from :: forall x.
SAM_V1_6_Program_Record_Identifier
-> Rep SAM_V1_6_Program_Record_Identifier x
$cto :: forall x.
Rep SAM_V1_6_Program_Record_Identifier x
-> SAM_V1_6_Program_Record_Identifier
to :: forall x.
Rep SAM_V1_6_Program_Record_Identifier x
-> SAM_V1_6_Program_Record_Identifier
Generic,Typeable)
instance Eq SAM_V1_6_Program_Record_Identifier where
SAM_V1_6_Program_Record_Identifier Seq Word8
sam_v1_6_program_record_identifier_tag1 ByteString
sam_v1_6_program_record_identifier_value1 == :: SAM_V1_6_Program_Record_Identifier
-> SAM_V1_6_Program_Record_Identifier -> Bool
== SAM_V1_6_Program_Record_Identifier Seq Word8
sam_v1_6_program_record_identifier_tag2 ByteString
sam_v1_6_program_record_identifier_value2 = Seq Word8
sam_v1_6_program_record_identifier_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_record_identifier_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_record_identifier_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_record_identifier_value2
instance Show SAM_V1_6_Program_Record_Identifier where
show :: SAM_V1_6_Program_Record_Identifier -> String
show (SAM_V1_6_Program_Record_Identifier Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Record_Identifier { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"
data SAM_V1_6_Program_Name = SAM_V1_6_Program_Name { SAM_V1_6_Program_Name -> Seq Word8
sam_v1_6_program_name_tag :: Seq Word8
, SAM_V1_6_Program_Name -> ByteString
sam_v1_6_program_name_value :: ByteString
}
deriving ((forall x. SAM_V1_6_Program_Name -> Rep SAM_V1_6_Program_Name x)
-> (forall x. Rep SAM_V1_6_Program_Name x -> SAM_V1_6_Program_Name)
-> Generic SAM_V1_6_Program_Name
forall x. Rep SAM_V1_6_Program_Name x -> SAM_V1_6_Program_Name
forall x. SAM_V1_6_Program_Name -> Rep SAM_V1_6_Program_Name x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SAM_V1_6_Program_Name -> Rep SAM_V1_6_Program_Name x
from :: forall x. SAM_V1_6_Program_Name -> Rep SAM_V1_6_Program_Name x
$cto :: forall x. Rep SAM_V1_6_Program_Name x -> SAM_V1_6_Program_Name
to :: forall x. Rep SAM_V1_6_Program_Name x -> SAM_V1_6_Program_Name
Generic,Typeable)
instance Eq SAM_V1_6_Program_Name where
SAM_V1_6_Program_Name Seq Word8
sam_v1_6_program_name_tag1 ByteString
sam_v1_6_program_name_value1 == :: SAM_V1_6_Program_Name -> SAM_V1_6_Program_Name -> Bool
== SAM_V1_6_Program_Name Seq Word8
sam_v1_6_program_name_tag2 ByteString
sam_v1_6_program_name_value2 = Seq Word8
sam_v1_6_program_name_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_name_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_name_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_name_value2
instance Show SAM_V1_6_Program_Name where
show :: SAM_V1_6_Program_Name -> String
show (SAM_V1_6_Program_Name Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Name { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"
data SAM_V1_6_Program_Command_Line = SAM_V1_6_Program_Command_Line { SAM_V1_6_Program_Command_Line -> Seq Word8
sam_v1_6_program_command_line_tag :: Seq Word8
, SAM_V1_6_Program_Command_Line -> ByteString
sam_v1_6_program_command_line_value :: ByteString
}
deriving ((forall x.
SAM_V1_6_Program_Command_Line
-> Rep SAM_V1_6_Program_Command_Line x)
-> (forall x.
Rep SAM_V1_6_Program_Command_Line x
-> SAM_V1_6_Program_Command_Line)
-> Generic SAM_V1_6_Program_Command_Line
forall x.
Rep SAM_V1_6_Program_Command_Line x
-> SAM_V1_6_Program_Command_Line
forall x.
SAM_V1_6_Program_Command_Line
-> Rep SAM_V1_6_Program_Command_Line x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Program_Command_Line
-> Rep SAM_V1_6_Program_Command_Line x
from :: forall x.
SAM_V1_6_Program_Command_Line
-> Rep SAM_V1_6_Program_Command_Line x
$cto :: forall x.
Rep SAM_V1_6_Program_Command_Line x
-> SAM_V1_6_Program_Command_Line
to :: forall x.
Rep SAM_V1_6_Program_Command_Line x
-> SAM_V1_6_Program_Command_Line
Generic,Typeable)
instance Eq SAM_V1_6_Program_Command_Line where
SAM_V1_6_Program_Command_Line Seq Word8
sam_v1_6_program_command_line_tag1 ByteString
sam_v1_6_program_command_line_value1 == :: SAM_V1_6_Program_Command_Line
-> SAM_V1_6_Program_Command_Line -> Bool
== SAM_V1_6_Program_Command_Line Seq Word8
sam_v1_6_program_command_line_tag2 ByteString
sam_v1_6_program_command_line_value2 = Seq Word8
sam_v1_6_program_command_line_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_command_line_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_command_line_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_command_line_value2
instance Show SAM_V1_6_Program_Command_Line where
show :: SAM_V1_6_Program_Command_Line -> String
show (SAM_V1_6_Program_Command_Line Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Command_Line { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"
data SAM_V1_6_Program_Previous_PG_ID = SAM_V1_6_Program_Previous_PG_ID { SAM_V1_6_Program_Previous_PG_ID -> Seq Word8
sam_v1_6_program_previous_pg_id_tag :: Seq Word8
, SAM_V1_6_Program_Previous_PG_ID -> ByteString
sam_v1_6_program_previous_pg_id_value :: ByteString
}
deriving ((forall x.
SAM_V1_6_Program_Previous_PG_ID
-> Rep SAM_V1_6_Program_Previous_PG_ID x)
-> (forall x.
Rep SAM_V1_6_Program_Previous_PG_ID x
-> SAM_V1_6_Program_Previous_PG_ID)
-> Generic SAM_V1_6_Program_Previous_PG_ID
forall x.
Rep SAM_V1_6_Program_Previous_PG_ID x
-> SAM_V1_6_Program_Previous_PG_ID
forall x.
SAM_V1_6_Program_Previous_PG_ID
-> Rep SAM_V1_6_Program_Previous_PG_ID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Program_Previous_PG_ID
-> Rep SAM_V1_6_Program_Previous_PG_ID x
from :: forall x.
SAM_V1_6_Program_Previous_PG_ID
-> Rep SAM_V1_6_Program_Previous_PG_ID x
$cto :: forall x.
Rep SAM_V1_6_Program_Previous_PG_ID x
-> SAM_V1_6_Program_Previous_PG_ID
to :: forall x.
Rep SAM_V1_6_Program_Previous_PG_ID x
-> SAM_V1_6_Program_Previous_PG_ID
Generic,Typeable)
instance Eq SAM_V1_6_Program_Previous_PG_ID where
SAM_V1_6_Program_Previous_PG_ID Seq Word8
sam_v1_6_program_previous_pg_id_tag1 ByteString
sam_v1_6_program_previous_pg_id_value1 == :: SAM_V1_6_Program_Previous_PG_ID
-> SAM_V1_6_Program_Previous_PG_ID -> Bool
== SAM_V1_6_Program_Previous_PG_ID Seq Word8
sam_v1_6_program_previous_pg_id_tag2 ByteString
sam_v1_6_program_previous_pg_id_value2 = Seq Word8
sam_v1_6_program_previous_pg_id_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_previous_pg_id_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_previous_pg_id_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_previous_pg_id_value2
instance Show SAM_V1_6_Program_Previous_PG_ID where
show :: SAM_V1_6_Program_Previous_PG_ID -> String
show (SAM_V1_6_Program_Previous_PG_ID Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Previous_PG_ID { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"
data SAM_V1_6_Program_Description = SAM_V1_6_Program_Description { SAM_V1_6_Program_Description -> Seq Word8
sam_v1_6_program_description_tag :: Seq Word8
, SAM_V1_6_Program_Description -> ByteString
sam_v1_6_program_description_value :: ByteString
}
deriving ((forall x.
SAM_V1_6_Program_Description -> Rep SAM_V1_6_Program_Description x)
-> (forall x.
Rep SAM_V1_6_Program_Description x -> SAM_V1_6_Program_Description)
-> Generic SAM_V1_6_Program_Description
forall x.
Rep SAM_V1_6_Program_Description x -> SAM_V1_6_Program_Description
forall x.
SAM_V1_6_Program_Description -> Rep SAM_V1_6_Program_Description x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Program_Description -> Rep SAM_V1_6_Program_Description x
from :: forall x.
SAM_V1_6_Program_Description -> Rep SAM_V1_6_Program_Description x
$cto :: forall x.
Rep SAM_V1_6_Program_Description x -> SAM_V1_6_Program_Description
to :: forall x.
Rep SAM_V1_6_Program_Description x -> SAM_V1_6_Program_Description
Generic,Typeable)
instance Eq SAM_V1_6_Program_Description where
SAM_V1_6_Program_Description Seq Word8
sam_v1_6_program_description_tag1 ByteString
sam_v1_6_program_description_value1 == :: SAM_V1_6_Program_Description
-> SAM_V1_6_Program_Description -> Bool
== SAM_V1_6_Program_Description Seq Word8
sam_v1_6_program_description_tag2 ByteString
sam_v1_6_program_description_value2 = Seq Word8
sam_v1_6_program_description_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_description_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_description_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_description_value2
instance Show SAM_V1_6_Program_Description where
show :: SAM_V1_6_Program_Description -> String
show (SAM_V1_6_Program_Description Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Description { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"
data SAM_V1_6_Program_Version = SAM_V1_6_Program_Version { SAM_V1_6_Program_Version -> Seq Word8
sam_v1_6_program_version_tag :: Seq Word8
, SAM_V1_6_Program_Version -> ByteString
sam_v1_6_program_version_value :: ByteString
}
deriving ((forall x.
SAM_V1_6_Program_Version -> Rep SAM_V1_6_Program_Version x)
-> (forall x.
Rep SAM_V1_6_Program_Version x -> SAM_V1_6_Program_Version)
-> Generic SAM_V1_6_Program_Version
forall x.
Rep SAM_V1_6_Program_Version x -> SAM_V1_6_Program_Version
forall x.
SAM_V1_6_Program_Version -> Rep SAM_V1_6_Program_Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SAM_V1_6_Program_Version -> Rep SAM_V1_6_Program_Version x
from :: forall x.
SAM_V1_6_Program_Version -> Rep SAM_V1_6_Program_Version x
$cto :: forall x.
Rep SAM_V1_6_Program_Version x -> SAM_V1_6_Program_Version
to :: forall x.
Rep SAM_V1_6_Program_Version x -> SAM_V1_6_Program_Version
Generic,Typeable)
instance Eq SAM_V1_6_Program_Version where
SAM_V1_6_Program_Version Seq Word8
sam_v1_6_program_version_tag1 ByteString
sam_v1_6_program_version_value1 == :: SAM_V1_6_Program_Version -> SAM_V1_6_Program_Version -> Bool
== SAM_V1_6_Program_Version Seq Word8
sam_v1_6_program_version_tag2 ByteString
sam_v1_6_program_version_value2 = Seq Word8
sam_v1_6_program_version_tag1 Seq Word8 -> Seq Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Seq Word8
sam_v1_6_program_version_tag2 Bool -> Bool -> Bool
&& ByteString
sam_v1_6_program_version_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
sam_v1_6_program_version_value2
instance Show SAM_V1_6_Program_Version where
show :: SAM_V1_6_Program_Version -> String
show (SAM_V1_6_Program_Version Seq Word8
tag ByteString
value) =
String
"SAM_V1_6_Program_Version { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"tag = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Seq Word8 -> String
forall a. Show a => a -> String
show Seq Word8
tag) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , 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
" }"