{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
module Data.BAM.Version1_6.BAM.Header.PG (
BAM_V1_6_Program(..),
BAM_V1_6_Program_Record_Identifier(..),
BAM_V1_6_Program_Name(..),
BAM_V1_6_Program_Command_Line(..),
BAM_V1_6_Program_Previous_PG_ID(..),
BAM_V1_6_Program_Description(..),
BAM_V1_6_Program_Version(..)
) where
import Data.ByteString
import Data.Data
import Generics.Deriving.Base
data BAM_V1_6_Program = BAM_V1_6_Program { BAM_V1_6_Program -> BAM_V1_6_Program_Record_Identifier
bam_v1_6_program_record_identifier :: BAM_V1_6_Program_Record_Identifier
, BAM_V1_6_Program -> Maybe BAM_V1_6_Program_Name
bam_v1_6_program_name :: Maybe BAM_V1_6_Program_Name
, BAM_V1_6_Program -> Maybe BAM_V1_6_Program_Command_Line
bam_v1_6_program_command_line :: Maybe BAM_V1_6_Program_Command_Line
, BAM_V1_6_Program -> Maybe BAM_V1_6_Program_Previous_PG_ID
bam_v1_6_program_previous_pg_id :: Maybe BAM_V1_6_Program_Previous_PG_ID
, BAM_V1_6_Program -> Maybe BAM_V1_6_Program_Description
bam_v1_6_program_description :: Maybe BAM_V1_6_Program_Description
, BAM_V1_6_Program -> Maybe BAM_V1_6_Program_Version
bam_v1_6_program_version :: Maybe BAM_V1_6_Program_Version
}
deriving ((forall x. BAM_V1_6_Program -> Rep BAM_V1_6_Program x)
-> (forall x. Rep BAM_V1_6_Program x -> BAM_V1_6_Program)
-> Generic BAM_V1_6_Program
forall x. Rep BAM_V1_6_Program x -> BAM_V1_6_Program
forall x. BAM_V1_6_Program -> Rep BAM_V1_6_Program x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BAM_V1_6_Program -> Rep BAM_V1_6_Program x
from :: forall x. BAM_V1_6_Program -> Rep BAM_V1_6_Program x
$cto :: forall x. Rep BAM_V1_6_Program x -> BAM_V1_6_Program
to :: forall x. Rep BAM_V1_6_Program x -> BAM_V1_6_Program
Generic,Typeable)
instance Eq BAM_V1_6_Program where
BAM_V1_6_Program BAM_V1_6_Program_Record_Identifier
bam_v1_6_program_record_identifier1
Maybe BAM_V1_6_Program_Name
bam_v1_6_program_name1
Maybe BAM_V1_6_Program_Command_Line
bam_v1_6_program_command_line1
Maybe BAM_V1_6_Program_Previous_PG_ID
bam_v1_6_program_previous_pg_id1
Maybe BAM_V1_6_Program_Description
bam_v1_6_program_description1
Maybe BAM_V1_6_Program_Version
bam_v1_6_program_version1 == :: BAM_V1_6_Program -> BAM_V1_6_Program -> Bool
==
BAM_V1_6_Program BAM_V1_6_Program_Record_Identifier
bam_v1_6_program_record_identifier2
Maybe BAM_V1_6_Program_Name
bam_v1_6_program_name2
Maybe BAM_V1_6_Program_Command_Line
bam_v1_6_program_command_line2
Maybe BAM_V1_6_Program_Previous_PG_ID
bam_v1_6_program_previous_pg_id2
Maybe BAM_V1_6_Program_Description
bam_v1_6_program_description2
Maybe BAM_V1_6_Program_Version
bam_v1_6_program_version2 =
BAM_V1_6_Program_Record_Identifier
bam_v1_6_program_record_identifier1 BAM_V1_6_Program_Record_Identifier
-> BAM_V1_6_Program_Record_Identifier -> Bool
forall a. Eq a => a -> a -> Bool
== BAM_V1_6_Program_Record_Identifier
bam_v1_6_program_record_identifier2 Bool -> Bool -> Bool
&&
Maybe BAM_V1_6_Program_Name
bam_v1_6_program_name1 Maybe BAM_V1_6_Program_Name -> Maybe BAM_V1_6_Program_Name -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe BAM_V1_6_Program_Name
bam_v1_6_program_name2 Bool -> Bool -> Bool
&&
Maybe BAM_V1_6_Program_Command_Line
bam_v1_6_program_command_line1 Maybe BAM_V1_6_Program_Command_Line
-> Maybe BAM_V1_6_Program_Command_Line -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe BAM_V1_6_Program_Command_Line
bam_v1_6_program_command_line2 Bool -> Bool -> Bool
&&
Maybe BAM_V1_6_Program_Previous_PG_ID
bam_v1_6_program_previous_pg_id1 Maybe BAM_V1_6_Program_Previous_PG_ID
-> Maybe BAM_V1_6_Program_Previous_PG_ID -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe BAM_V1_6_Program_Previous_PG_ID
bam_v1_6_program_previous_pg_id2 Bool -> Bool -> Bool
&&
Maybe BAM_V1_6_Program_Description
bam_v1_6_program_description1 Maybe BAM_V1_6_Program_Description
-> Maybe BAM_V1_6_Program_Description -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe BAM_V1_6_Program_Description
bam_v1_6_program_description2 Bool -> Bool -> Bool
&&
Maybe BAM_V1_6_Program_Version
bam_v1_6_program_version1 Maybe BAM_V1_6_Program_Version
-> Maybe BAM_V1_6_Program_Version -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe BAM_V1_6_Program_Version
bam_v1_6_program_version2
instance Show BAM_V1_6_Program where
show :: BAM_V1_6_Program -> String
show (BAM_V1_6_Program BAM_V1_6_Program_Record_Identifier
record_identifier Maybe BAM_V1_6_Program_Name
name Maybe BAM_V1_6_Program_Command_Line
command_line Maybe BAM_V1_6_Program_Previous_PG_ID
previous_pg_id Maybe BAM_V1_6_Program_Description
description Maybe BAM_V1_6_Program_Version
version) =
String
"BAM_V1_6_Program { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"rbam_v1_6_program_record_identifier = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(BAM_V1_6_Program_Record_Identifier -> String
forall a. Show a => a -> String
show BAM_V1_6_Program_Record_Identifier
record_identifier) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , bam_v1_6_program_name = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe BAM_V1_6_Program_Name -> String
forall a. Show a => a -> String
show Maybe BAM_V1_6_Program_Name
name) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , bam_v1_6_program_command_line = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe BAM_V1_6_Program_Command_Line -> String
forall a. Show a => a -> String
show Maybe BAM_V1_6_Program_Command_Line
command_line) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , bam_v1_6_program_previous_pg_id = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe BAM_V1_6_Program_Previous_PG_ID -> String
forall a. Show a => a -> String
show Maybe BAM_V1_6_Program_Previous_PG_ID
previous_pg_id) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , bam_v1_6_program_description = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe BAM_V1_6_Program_Description -> String
forall a. Show a => a -> String
show Maybe BAM_V1_6_Program_Description
description) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" , bam_v1_6_program_version = " String -> ShowS
forall a. [a] -> [a] -> [a]
++
(Maybe BAM_V1_6_Program_Version -> String
forall a. Show a => a -> String
show Maybe BAM_V1_6_Program_Version
version) String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
" }"
newtype BAM_V1_6_Program_Record_Identifier = BAM_V1_6_Program_Record_Identifier { BAM_V1_6_Program_Record_Identifier -> ByteString
bam_v1_6_program_record_identifier_value :: ByteString
}
deriving ((forall x.
BAM_V1_6_Program_Record_Identifier
-> Rep BAM_V1_6_Program_Record_Identifier x)
-> (forall x.
Rep BAM_V1_6_Program_Record_Identifier x
-> BAM_V1_6_Program_Record_Identifier)
-> Generic BAM_V1_6_Program_Record_Identifier
forall x.
Rep BAM_V1_6_Program_Record_Identifier x
-> BAM_V1_6_Program_Record_Identifier
forall x.
BAM_V1_6_Program_Record_Identifier
-> Rep BAM_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.
BAM_V1_6_Program_Record_Identifier
-> Rep BAM_V1_6_Program_Record_Identifier x
from :: forall x.
BAM_V1_6_Program_Record_Identifier
-> Rep BAM_V1_6_Program_Record_Identifier x
$cto :: forall x.
Rep BAM_V1_6_Program_Record_Identifier x
-> BAM_V1_6_Program_Record_Identifier
to :: forall x.
Rep BAM_V1_6_Program_Record_Identifier x
-> BAM_V1_6_Program_Record_Identifier
Generic,Typeable)
instance Eq BAM_V1_6_Program_Record_Identifier where
BAM_V1_6_Program_Record_Identifier ByteString
bam_v1_6_program_record_identifier_value1 == :: BAM_V1_6_Program_Record_Identifier
-> BAM_V1_6_Program_Record_Identifier -> Bool
==
BAM_V1_6_Program_Record_Identifier ByteString
bam_v1_6_program_record_identifier_value2 =
ByteString
bam_v1_6_program_record_identifier_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_record_identifier_value2
instance Show BAM_V1_6_Program_Record_Identifier where
show :: BAM_V1_6_Program_Record_Identifier -> String
show (BAM_V1_6_Program_Record_Identifier ByteString
value) =
String
"BAM_V1_6_Program_Record_Identifier { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_record_identifier_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
" }"
newtype BAM_V1_6_Program_Name = BAM_V1_6_Program_Name { BAM_V1_6_Program_Name -> ByteString
bam_v1_6_program_name_value :: ByteString
}
deriving ((forall x. BAM_V1_6_Program_Name -> Rep BAM_V1_6_Program_Name x)
-> (forall x. Rep BAM_V1_6_Program_Name x -> BAM_V1_6_Program_Name)
-> Generic BAM_V1_6_Program_Name
forall x. Rep BAM_V1_6_Program_Name x -> BAM_V1_6_Program_Name
forall x. BAM_V1_6_Program_Name -> Rep BAM_V1_6_Program_Name x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BAM_V1_6_Program_Name -> Rep BAM_V1_6_Program_Name x
from :: forall x. BAM_V1_6_Program_Name -> Rep BAM_V1_6_Program_Name x
$cto :: forall x. Rep BAM_V1_6_Program_Name x -> BAM_V1_6_Program_Name
to :: forall x. Rep BAM_V1_6_Program_Name x -> BAM_V1_6_Program_Name
Generic,Typeable)
instance Eq BAM_V1_6_Program_Name where
BAM_V1_6_Program_Name ByteString
bam_v1_6_program_name_value1 == :: BAM_V1_6_Program_Name -> BAM_V1_6_Program_Name -> Bool
==
BAM_V1_6_Program_Name ByteString
bam_v1_6_program_name_value2 =
ByteString
bam_v1_6_program_name_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_name_value2
instance Show BAM_V1_6_Program_Name where
show :: BAM_V1_6_Program_Name -> String
show (BAM_V1_6_Program_Name ByteString
value) =
String
"BAM_V1_6_Program_Name { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_name_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
" }"
newtype BAM_V1_6_Program_Command_Line = BAM_V1_6_Program_Command_Line { BAM_V1_6_Program_Command_Line -> ByteString
bam_v1_6_program_command_line_value :: ByteString
}
deriving ((forall x.
BAM_V1_6_Program_Command_Line
-> Rep BAM_V1_6_Program_Command_Line x)
-> (forall x.
Rep BAM_V1_6_Program_Command_Line x
-> BAM_V1_6_Program_Command_Line)
-> Generic BAM_V1_6_Program_Command_Line
forall x.
Rep BAM_V1_6_Program_Command_Line x
-> BAM_V1_6_Program_Command_Line
forall x.
BAM_V1_6_Program_Command_Line
-> Rep BAM_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.
BAM_V1_6_Program_Command_Line
-> Rep BAM_V1_6_Program_Command_Line x
from :: forall x.
BAM_V1_6_Program_Command_Line
-> Rep BAM_V1_6_Program_Command_Line x
$cto :: forall x.
Rep BAM_V1_6_Program_Command_Line x
-> BAM_V1_6_Program_Command_Line
to :: forall x.
Rep BAM_V1_6_Program_Command_Line x
-> BAM_V1_6_Program_Command_Line
Generic,Typeable)
instance Eq BAM_V1_6_Program_Command_Line where
BAM_V1_6_Program_Command_Line ByteString
bam_v1_6_program_command_line_value1 == :: BAM_V1_6_Program_Command_Line
-> BAM_V1_6_Program_Command_Line -> Bool
==
BAM_V1_6_Program_Command_Line ByteString
bam_v1_6_program_command_line_value2 =
ByteString
bam_v1_6_program_command_line_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_command_line_value2
instance Show BAM_V1_6_Program_Command_Line where
show :: BAM_V1_6_Program_Command_Line -> String
show (BAM_V1_6_Program_Command_Line ByteString
value) =
String
"BAM_V1_6_Program_Command_Line { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_command_line_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
" }"
newtype BAM_V1_6_Program_Previous_PG_ID = BAM_V1_6_Program_Previous_PG_ID { BAM_V1_6_Program_Previous_PG_ID -> ByteString
bam_v1_6_program_previous_pg_id_value :: ByteString
}
deriving ((forall x.
BAM_V1_6_Program_Previous_PG_ID
-> Rep BAM_V1_6_Program_Previous_PG_ID x)
-> (forall x.
Rep BAM_V1_6_Program_Previous_PG_ID x
-> BAM_V1_6_Program_Previous_PG_ID)
-> Generic BAM_V1_6_Program_Previous_PG_ID
forall x.
Rep BAM_V1_6_Program_Previous_PG_ID x
-> BAM_V1_6_Program_Previous_PG_ID
forall x.
BAM_V1_6_Program_Previous_PG_ID
-> Rep BAM_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.
BAM_V1_6_Program_Previous_PG_ID
-> Rep BAM_V1_6_Program_Previous_PG_ID x
from :: forall x.
BAM_V1_6_Program_Previous_PG_ID
-> Rep BAM_V1_6_Program_Previous_PG_ID x
$cto :: forall x.
Rep BAM_V1_6_Program_Previous_PG_ID x
-> BAM_V1_6_Program_Previous_PG_ID
to :: forall x.
Rep BAM_V1_6_Program_Previous_PG_ID x
-> BAM_V1_6_Program_Previous_PG_ID
Generic,Typeable)
instance Eq BAM_V1_6_Program_Previous_PG_ID where
BAM_V1_6_Program_Previous_PG_ID ByteString
bam_v1_6_program_previous_pg_id_value1 == :: BAM_V1_6_Program_Previous_PG_ID
-> BAM_V1_6_Program_Previous_PG_ID -> Bool
==
BAM_V1_6_Program_Previous_PG_ID ByteString
bam_v1_6_program_previous_pg_id_value2 =
ByteString
bam_v1_6_program_previous_pg_id_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_previous_pg_id_value2
instance Show BAM_V1_6_Program_Previous_PG_ID where
show :: BAM_V1_6_Program_Previous_PG_ID -> String
show (BAM_V1_6_Program_Previous_PG_ID ByteString
value) =
String
"BAM_V1_6_Program_Previous_PG_ID { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_previous_pg_id_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
" }"
newtype BAM_V1_6_Program_Description = BAM_V1_6_Program_Description { BAM_V1_6_Program_Description -> ByteString
bam_v1_6_program_description_value :: ByteString
}
deriving ((forall x.
BAM_V1_6_Program_Description -> Rep BAM_V1_6_Program_Description x)
-> (forall x.
Rep BAM_V1_6_Program_Description x -> BAM_V1_6_Program_Description)
-> Generic BAM_V1_6_Program_Description
forall x.
Rep BAM_V1_6_Program_Description x -> BAM_V1_6_Program_Description
forall x.
BAM_V1_6_Program_Description -> Rep BAM_V1_6_Program_Description x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
BAM_V1_6_Program_Description -> Rep BAM_V1_6_Program_Description x
from :: forall x.
BAM_V1_6_Program_Description -> Rep BAM_V1_6_Program_Description x
$cto :: forall x.
Rep BAM_V1_6_Program_Description x -> BAM_V1_6_Program_Description
to :: forall x.
Rep BAM_V1_6_Program_Description x -> BAM_V1_6_Program_Description
Generic,Typeable)
instance Eq BAM_V1_6_Program_Description where
BAM_V1_6_Program_Description ByteString
bam_v1_6_program_description_value1 == :: BAM_V1_6_Program_Description
-> BAM_V1_6_Program_Description -> Bool
==
BAM_V1_6_Program_Description ByteString
bam_v1_6_program_description_value2 =
ByteString
bam_v1_6_program_description_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_description_value2
instance Show BAM_V1_6_Program_Description where
show :: BAM_V1_6_Program_Description -> String
show (BAM_V1_6_Program_Description ByteString
value) =
String
"BAM_V1_6_Program_Description { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_description_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
" }"
newtype BAM_V1_6_Program_Version = BAM_V1_6_Program_Version { BAM_V1_6_Program_Version -> ByteString
bam_v1_6_program_version_value :: ByteString
}
deriving ((forall x.
BAM_V1_6_Program_Version -> Rep BAM_V1_6_Program_Version x)
-> (forall x.
Rep BAM_V1_6_Program_Version x -> BAM_V1_6_Program_Version)
-> Generic BAM_V1_6_Program_Version
forall x.
Rep BAM_V1_6_Program_Version x -> BAM_V1_6_Program_Version
forall x.
BAM_V1_6_Program_Version -> Rep BAM_V1_6_Program_Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
BAM_V1_6_Program_Version -> Rep BAM_V1_6_Program_Version x
from :: forall x.
BAM_V1_6_Program_Version -> Rep BAM_V1_6_Program_Version x
$cto :: forall x.
Rep BAM_V1_6_Program_Version x -> BAM_V1_6_Program_Version
to :: forall x.
Rep BAM_V1_6_Program_Version x -> BAM_V1_6_Program_Version
Generic,Typeable)
instance Eq BAM_V1_6_Program_Version where
BAM_V1_6_Program_Version ByteString
bam_v1_6_program_version_value1 == :: BAM_V1_6_Program_Version -> BAM_V1_6_Program_Version -> Bool
==
BAM_V1_6_Program_Version ByteString
bam_v1_6_program_version_value2 =
ByteString
bam_v1_6_program_version_value1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bam_v1_6_program_version_value2
instance Show BAM_V1_6_Program_Version where
show :: BAM_V1_6_Program_Version -> String
show (BAM_V1_6_Program_Version ByteString
value) =
String
"BAM_V1_6_Program_Version { " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"bam_v1_6_program_version_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
" }"