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

-- |
-- Module      :  Data.SAM.Version1_6.Read.Parser.Alignment.FOPT
-- Copyright   :  (c) Matthew Mosior 2023
-- 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.SAM.Version1_6.Read.Parser.Alignment.FOPT ( -- * SAM_V1_6 parser - alignment section - fopt field 
                                                        parse_SAM_V1_6_Alignment_FOPT
                                                      ) where

import Data.SAM.Version1_6.Alignment.FOPT
import Data.SAM.Version1_6.Read.Error

import           Data.Attoparsec.ByteString.Char8  as DABC8 (isEndOfLine)
import           Data.Attoparsec.ByteString.Lazy   as DABL
import qualified Data.ByteString.Char8             as DBC8
import           Text.Regex.PCRE.Heavy

-- | Defines a parser for the optional fopt field of alignment section of the SAM v1.6 file format.
--
-- See the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
parse_SAM_V1_6_Alignment_FOPT :: Parser SAM_V1_6_Alignment_FOPT
parse_SAM_V1_6_Alignment_FOPT :: Parser SAM_V1_6_Alignment_FOPT
parse_SAM_V1_6_Alignment_FOPT = do
  ByteString
alignmentfoptfieldtag <- do ByteString
alignmentfoptfieldtagp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
                              -- Parse FOPT tag of the alignment section.
                              case (ByteString
alignmentfoptfieldtagp 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
$ SAM_V1_6_Error -> String
forall a. Show a => a -> String
show SAM_V1_6_Error
SAM_V1_6_Error_Alignment_FOPT_Tag_Incorrect_Format
                                Bool
True  -> -- FOPT 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
alignmentfoptfieldtagp
  Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
  ()
_ <- do ByteString
alignmentfoptfieldtypep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
          -- Parse FOPT type of the alignment section.
          case (ByteString
alignmentfoptfieldtypep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[f]|]) 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
$ SAM_V1_6_Error -> String
forall a. Show a => a -> String
show SAM_V1_6_Error
SAM_V1_6_Error_Alignment_FOPT_Type_Incorrect_Format
            Bool
True  -> -- FOPT type is in the accepted format.
                     () -> Parser ByteString ()
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
  Float
alignmentfoptfieldvalue <- do ByteString
alignmentfoptfieldvaluep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (\Word8
x -> Word8
x Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09 Bool -> Bool -> Bool
|| Word8 -> Bool
isEndOfLine Word8
x)
                                -- Parse FOPT value of the alignment section.
                                case (ByteString
alignmentfoptfieldvaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[-+]?[0-9]*\.?[0-9]+([eE][-+]?[0-9]+)?|]) of
                                  Bool
False -> String -> Parser ByteString Float
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ByteString Float)
-> String -> Parser ByteString Float
forall a b. (a -> b) -> a -> b
$ SAM_V1_6_Error -> String
forall a. Show a => a -> String
show SAM_V1_6_Error
SAM_V1_6_Error_Alignment_FOPT_Value_Incorrect_Format
                                  Bool
True  -> -- FOPT value is in the accepted format.
                                           case (ByteString -> Maybe (Integer, ByteString)
DBC8.readInteger ByteString
alignmentfoptfieldvaluep) of
                                             Maybe (Integer, ByteString)
Nothing                                 -> Float -> Parser ByteString Float
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Float
1)
                                             Just (Integer
alignmentfoptfieldvalueinteger,ByteString
_) -> Float -> Parser ByteString Float
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float -> Parser ByteString Float)
-> Float -> Parser ByteString Float
forall a b. (a -> b) -> a -> b
$ (Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
alignmentfoptfieldvalueinteger :: Float)
  SAM_V1_6_Alignment_FOPT -> Parser SAM_V1_6_Alignment_FOPT
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return SAM_V1_6_Alignment_FOPT { sam_v1_6_alignment_fopt_tag :: ByteString
sam_v1_6_alignment_fopt_tag   = ByteString
alignmentfoptfieldtag
                                 , sam_v1_6_alignment_fopt_value :: Float
sam_v1_6_alignment_fopt_value = Float
alignmentfoptfieldvalue
                                 }