hs-samtools-0.9.0.0: Read and write SAM, BAM, and CRAM files.
Copyright(c) Matthew Mosior 2023
LicenseBSD-style
Maintainermattm.github@gmail.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SAM.Version1_6.Alignment.BOPT

Description

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 library for the above warning text.

Description

This library enables the decoding/encoding of SAM, BAM and CRAM file formats.

Synopsis

SAM version 1.6 alignment optional fields data type

data SAM_V1_6_Alignment_BOPT Source #

Custom SAM (version 1.6) SAM_V1_6_Alignment_BOPT data type.

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT = D1 ('MetaData "SAM_V1_6_Alignment_BOPT" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int8") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Int8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word8") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Word8)) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int16") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Int16)))) :*: ((S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word16") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Word16)) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int32") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Int32))) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word32") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Word32)) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_float") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SAM_V1_6_Alignment_BOPT_Float))))))

data SAM_V1_6_Alignment_BOPT_Int8 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Int8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Int8 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Int8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Int8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int8 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Int8" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Int8" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int8_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int8_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int8_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Int8)))))

data SAM_V1_6_Alignment_BOPT_Word8 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Word8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Word8 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Word8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Word8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word8 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word8 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Word8" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Word8" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word8_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word8_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word8_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)))))

data SAM_V1_6_Alignment_BOPT_Int16 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Int16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Int16 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Int16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Int16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int16 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Int16" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Int16" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int16_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int16_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int16_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Int16)))))

data SAM_V1_6_Alignment_BOPT_Word16 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Word16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Word16 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Word16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Word16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word16 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word16 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Word16" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Word16" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word16_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word16_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word16_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word16)))))

data SAM_V1_6_Alignment_BOPT_Int32 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Int32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Int32 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Int32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Int32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Int32 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Int32" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Int32" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int32_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int32_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_int32_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Int32)))))

data SAM_V1_6_Alignment_BOPT_Word32 Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Word32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Word32 :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Word32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Word32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word32 Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Word32 = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Word32" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Word32" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word32_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word32_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_word32_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word32)))))

data SAM_V1_6_Alignment_BOPT_Float Source #

cCsSiIf of the last optional field (type B).

See section 1.5 of the SAM v1.6 specification documentation.

Instances

Instances details
Generic SAM_V1_6_Alignment_BOPT_Float Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Associated Types

type Rep SAM_V1_6_Alignment_BOPT_Float :: Type -> Type #

Show SAM_V1_6_Alignment_BOPT_Float Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

Eq SAM_V1_6_Alignment_BOPT_Float Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Float Source # 
Instance details

Defined in Data.SAM.Version1_6.Alignment.BOPT

type Rep SAM_V1_6_Alignment_BOPT_Float = D1 ('MetaData "SAM_V1_6_Alignment_BOPT_Float" "Data.SAM.Version1_6.Alignment.BOPT" "hs-samtools-0.9.0.0-inplace" 'False) (C1 ('MetaCons "SAM_V1_6_Alignment_BOPT_Float" 'PrefixI 'True) (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_float_tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Word8)) :*: (S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_float_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "sam_v1_6_alignment_bopt_float_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Float)))))