{-# 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                 #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}

-- |
-- Module      :  Data.SAM.Version1_6.Read.Parser.Header.PG.Base
-- 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.PG.Base ( -- * SAM_V1_6 parser - header section (Program)
                                                        parse_SAM_V1_6_Program
                                                      ) where

import Data.SAM.Version1_6.Header
import Data.SAM.Version1_6.Read.Error
import Data.SAM.Version1_6.Read.Parser.Header.PG.ID
import Data.SAM.Version1_6.Read.Parser.Header.PG.PN
import Data.SAM.Version1_6.Read.Parser.Header.PG.CL
import Data.SAM.Version1_6.Read.Parser.Header.PG.PP
import Data.SAM.Version1_6.Read.Parser.Header.PG.DS
import Data.SAM.Version1_6.Read.Parser.Header.PG.VN

import Data.Attoparsec.ByteString.Lazy   as DABL
import Text.Regex.PCRE.Heavy

-- | Make a parser optional, return Nothing if there is no match.
maybeOption :: Parser a
            -> Parser (Maybe a)
maybeOption :: forall a. Parser a -> Parser (Maybe a)
maybeOption Parser a
p = Maybe a
-> Parser ByteString (Maybe a) -> Parser ByteString (Maybe a)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
option Maybe a
forall a. Maybe a
Nothing (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Parser a -> Parser ByteString (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser a
p)

-- | @"SAM_V1_6_Program"@ parser.
-- Defines a parser for @PG 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_Program :: Parser SAM_V1_6_Program
parse_SAM_V1_6_Program :: Parser SAM_V1_6_Program
parse_SAM_V1_6_Program = do
  ByteString
_         <- do ByteString
pgheaderp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09)
                  -- Parse @PG tag of the header section.
                  case (ByteString
pgheaderp ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[@][P][G]|]) 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_Program_Tag_Incorrect_Format 
                    Bool
True  -> -- @PG 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
pgheaderp
  Word8
_         <- Word8 -> Parser Word8
word8 Word8
09
  -- This parser assumes that the ID tag always appears first, followed by
  -- the PN, CL, PP,
  -- DS and VN tags if they exist, in that order.
  SAM_V1_6_Program_Record_Identifier
id <- Parser SAM_V1_6_Program_Record_Identifier
parse_SAM_V1_6_SAM_V1_6_Program_ID
  Word8
_  <- Word8 -> Parser Word8
word8 Word8
09
  Maybe SAM_V1_6_Program_Name
pn <- Parser SAM_V1_6_Program_Name
-> Parser (Maybe SAM_V1_6_Program_Name)
forall a. Parser a -> Parser (Maybe a)
maybeOption Parser SAM_V1_6_Program_Name
parse_SAM_V1_6_SAM_V1_6_Program_PN
  Word8
_  <- Word8 -> Parser Word8
word8 Word8
09
  Maybe SAM_V1_6_Program_Command_Line
cl <- Parser SAM_V1_6_Program_Command_Line
-> Parser (Maybe SAM_V1_6_Program_Command_Line)
forall a. Parser a -> Parser (Maybe a)
maybeOption Parser SAM_V1_6_Program_Command_Line
parse_SAM_V1_6_SAM_V1_6_Program_CL
  Word8
_  <- Word8 -> Parser Word8
word8 Word8
09
  Maybe SAM_V1_6_Program_Previous_PG_ID
pp <- Parser SAM_V1_6_Program_Previous_PG_ID
-> Parser (Maybe SAM_V1_6_Program_Previous_PG_ID)
forall a. Parser a -> Parser (Maybe a)
maybeOption Parser SAM_V1_6_Program_Previous_PG_ID
parse_SAM_V1_6_SAM_V1_6_Program_PP
  Word8
_  <- Word8 -> Parser Word8
word8 Word8
09
  Maybe SAM_V1_6_Program_Description
ds <- Parser SAM_V1_6_Program_Description
-> Parser (Maybe SAM_V1_6_Program_Description)
forall a. Parser a -> Parser (Maybe a)
maybeOption Parser SAM_V1_6_Program_Description
parse_SAM_V1_6_SAM_V1_6_Program_DS
  Word8
_  <- Word8 -> Parser Word8
word8 Word8
09
  Maybe SAM_V1_6_Program_Version
vn <- Parser SAM_V1_6_Program_Version
-> Parser (Maybe SAM_V1_6_Program_Version)
forall a. Parser a -> Parser (Maybe a)
maybeOption Parser SAM_V1_6_Program_Version
parse_SAM_V1_6_SAM_V1_6_Program_VN
  SAM_V1_6_Program -> Parser SAM_V1_6_Program
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return SAM_V1_6_Program { sam_v1_6_program_record_identifier :: SAM_V1_6_Program_Record_Identifier
sam_v1_6_program_record_identifier = SAM_V1_6_Program_Record_Identifier
id
                          , sam_v1_6_program_name :: Maybe SAM_V1_6_Program_Name
sam_v1_6_program_name              = Maybe SAM_V1_6_Program_Name
pn
                          , sam_v1_6_program_command_line :: Maybe SAM_V1_6_Program_Command_Line
sam_v1_6_program_command_line      = Maybe SAM_V1_6_Program_Command_Line
cl
                          , sam_v1_6_program_previous_pg_id :: Maybe SAM_V1_6_Program_Previous_PG_ID
sam_v1_6_program_previous_pg_id    = Maybe SAM_V1_6_Program_Previous_PG_ID
pp
                          , sam_v1_6_program_description :: Maybe SAM_V1_6_Program_Description
sam_v1_6_program_description       = Maybe SAM_V1_6_Program_Description
ds
                          , sam_v1_6_program_version :: Maybe SAM_V1_6_Program_Version
sam_v1_6_program_version           = Maybe SAM_V1_6_Program_Version
vn
                          }