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

-- |
-- Module      :  Data.SAM.Version1_6.Read.Parser.Header.RG.PL
-- 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.Header.RG.PL ( -- * SAM_V1_6 parser - header section (Read group) - PL tag
                                                      parse_SAM_V1_6_SAM_V1_6_Read_Group_PL
                                                    ) where

import Data.SAM.Version1_6.Header
import Data.SAM.Version1_6.Read.Error

import           Data.Attoparsec.ByteString.Lazy   as DABL
import qualified Data.ByteString                   as DB   (unpack)
import           Data.Sequence                     as DSeq
import           Text.Regex.PCRE.Heavy

-- | Defines a parser for the PL tag of the @RG tag 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_SAM_V1_6_Read_Group_PL :: Parser SAM_V1_6_Read_Group_Platform 
parse_SAM_V1_6_SAM_V1_6_Read_Group_PL :: Parser SAM_V1_6_Read_Group_Platform
parse_SAM_V1_6_SAM_V1_6_Read_Group_PL = do
  ByteString
rgheaderplatformtag <- do ByteString
rgheaderplatformtagp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
                            -- Parse PL tag of the header section.
                            case (ByteString
rgheaderplatformtagp ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[P][L]|]) 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_Read_Group_Platform_Incorrect_Format
                              Bool
True  -> -- PL 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
rgheaderplatformtagp
  Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
  ByteString
rgheaderplatformvalue <- do ByteString
rgheaderplatformvaluep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09)
                              -- Parse PL value of the header section.
                              case (ByteString
rgheaderplatformvaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[C][A][P][I][L][L][A][R][Y]|[D][N][B][S][E][Q]|[E][L][E][M][E][N][T]|[H][E][L][I][C][O][S]|[I][L][L][U][M][I][N][A]|[I][O][N][T][O][R][R][E][N][T]|[L][S][4][5][4]|[O][N][T]|[P][A][C][B][I][O]|[S][O][L][I][D]|[U][L][T][I][M][A]|]) 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_Read_Group_Platform_Incorrect_Format
                                Bool
True  -> -- PL 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
rgheaderplatformvaluep
  SAM_V1_6_Read_Group_Platform -> Parser SAM_V1_6_Read_Group_Platform
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return SAM_V1_6_Read_Group_Platform { sam_v1_6_read_group_platform_tag :: Seq Word8
sam_v1_6_read_group_platform_tag   = [Word8] -> Seq Word8
forall a. [a] -> Seq a
DSeq.fromList ([Word8] -> Seq Word8) -> [Word8] -> Seq Word8
forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
DB.unpack ByteString
rgheaderplatformtag
                                      , sam_v1_6_read_group_platform_value :: ByteString
sam_v1_6_read_group_platform_value = ByteString
rgheaderplatformvalue
                                      }