{-# LANGUAGE DeriveDataTypeable    #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists       #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE MultiWayIf            #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}
{-# Language QuasiQuotes           #-}

-- |
-- Module      :  Data.BAM.Version1_6.Read.Parser.BAM.Alignment.OptionalFields.HOPT
-- Copyright   :  (c) Matthew Mosior 2024
-- 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.BAM.Version1_6.Read.Parser.BAM.Alignment.OptionalFields.HOPT ( -- * BAM_V1_6 parser - alignment section - hopt field 
                                                                           parse_BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
                                                                         ) where

import Data.BAM.Version1_6.BAM.Alignment.OptionalFields.HOPT
import Data.BAM.Version1_6.Internal
import Data.BAM.Version1_6.Read.Error

import Data.ByteString.Base16            as DBB16
import Data.Base16.Types                 as DBB16T
import Data.Attoparsec.ByteString.Lazy   as DABL
import Data.Sequence                     as DSeq
import Text.Regex.PCRE.Heavy

-- | Defines a parser for the optional hopt field of alignment section of the BAM v1.6 file format.
--
-- See the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
parse_BAM_V1_6_BAM_Alignment_OptionalFields_HOPT :: Parser BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
parse_BAM_V1_6_BAM_Alignment_OptionalFields_HOPT :: Parser BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
parse_BAM_V1_6_BAM_Alignment_OptionalFields_HOPT = do
  ByteString
alignmenthoptfieldtag <- do
    ByteString
alignmenthoptfieldtagp <-
      Int -> Parser ByteString ByteString
DABL.take Int
2
    -- Parse HOPT tag of the alignment section.
    case (ByteString
alignmenthoptfieldtagp ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[A-Za-z][A-Za-z0-9]|]) of
      Bool
False ->
        String -> Parser ByteString ByteString
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ByteString ByteString)
-> String -> Parser ByteString ByteString
forall a b. (a -> b) -> a -> b
$
          BAM_V1_6_Read_Error -> String
forall a. Show a => a -> String
show BAM_V1_6_Read_Error
BAM_V1_6_Read_Error_Alignment_HOPT_Tag_Incorrect_Format
      Bool
True  ->
        -- HOPT tag is in the accepted format. 
        ByteString -> Parser ByteString ByteString
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
alignmenthoptfieldtagp
  ()
_ <- do
    ByteString
alignmenthoptfieldtypep <-
      Int -> Parser ByteString ByteString
DABL.take Int
1
    -- Parse HOPT type of the alignment section.
    case (ByteString
alignmenthoptfieldtypep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[H]|]) of
      Bool
False ->
        String -> Parser ByteString ()
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ByteString ()) -> String -> Parser ByteString ()
forall a b. (a -> b) -> a -> b
$
          BAM_V1_6_Read_Error -> String
forall a. Show a => a -> String
show BAM_V1_6_Read_Error
BAM_V1_6_Read_Error_Alignment_HOPT_Type_Incorrect_Format
      Bool
True  ->
        -- HOPT type is in the accepted format.
        () -> Parser ByteString ()
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  [ByteString]
alignmenthoptfieldvalue <- do
    ByteString
alignmenthoptfieldvaluep <-
      (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (\Word8
x -> Word8
x Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x00)
    -- Parse HOPT value of the alignment section.
    case (ByteString
alignmenthoptfieldvaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|([0-9A-F][0-9A-F])*|]) of
      Bool
False ->
        String -> Parser ByteString [ByteString]
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ByteString [ByteString])
-> String -> Parser ByteString [ByteString]
forall a b. (a -> b) -> a -> b
$
          BAM_V1_6_Read_Error -> String
forall a. Show a => a -> String
show BAM_V1_6_Read_Error
BAM_V1_6_Read_Error_Alignment_HOPT_Value_Incorrect_Format
      Bool
True  ->
        -- HOPT value is in the accepted format.
        [ByteString] -> Parser ByteString [ByteString]
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ([ByteString] -> Parser ByteString [ByteString])
-> [ByteString] -> Parser ByteString [ByteString]
forall a b. (a -> b) -> a -> b
$
          (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
Prelude.map (\ByteString
currenthexvalue -> do
                         case (ByteString -> Bool
DBB16.isBase16 ByteString
alignmenthoptfieldvaluep) of
                           Bool
False ->
                             String -> ByteString
forall a. HasCallStack => String -> a
error (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$
                               BAM_V1_6_Read_Error -> String
forall a. Show a => a -> String
show BAM_V1_6_Read_Error
BAM_V1_6_Read_Error_Alignment_HOPT_Value_Incorrect_Format
                           Bool
True  ->
                             Base16 ByteString -> ByteString
DBB16.decodeBase16    (Base16 ByteString -> ByteString)
-> Base16 ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
                               ByteString -> Base16 ByteString
forall a. a -> Base16 a
DBB16T.assertBase16 ByteString
currenthexvalue
                      ) ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$
          ( Int -> ByteString -> [ByteString]
splitByteString Int
2
                            ByteString
alignmenthoptfieldvaluep
          )
  ByteString
_ <-
    Int -> Parser ByteString ByteString
DABL.take Int
1
  BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
-> Parser BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return BAM_V1_6_BAM_Alignment_OptionalFields_HOPT
           { bam_v1_6_bam_alignment_optionalfields_hopt_tag :: ByteString
bam_v1_6_bam_alignment_optionalfields_hopt_tag   = ByteString
alignmenthoptfieldtag
           , bam_v1_6_bam_alignment_optionalfields_hopt_value :: Seq ByteString
bam_v1_6_bam_alignment_optionalfields_hopt_value = [ByteString] -> Seq ByteString
forall a. [a] -> Seq a
DSeq.fromList [ByteString]
alignmenthoptfieldvalue
           }