{-# 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                 #-}
{-# 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 Control.Applicative.Permutations           (intercalateEffect,toPermutation,toPermutationWithDefault)
import Data.Attoparsec.ByteString.Char8  as DABC8 (endOfLine)
import Data.Attoparsec.ByteString.Lazy   as DABL
import Text.Regex.PCRE.Heavy

-- | @"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
  ()
_         <- do ByteString
pgheaderp <- (Word8 -> Bool) -> Parser 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 ()
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_Program_Tag_Incorrect_Format 
                    Bool
True  -> -- @PG tag 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
09
  -- This parser assumes that the
  -- ID, PN, CL, PP, DS, and VN tags can appear in any order.
  SAM_V1_6_Program
pg <- Parser Word8
-> Permutation (Parser ByteString) SAM_V1_6_Program
-> Parser SAM_V1_6_Program
forall (m :: * -> *) b a.
Alternative m =>
m b -> Permutation m a -> m a
intercalateEffect (Word8 -> Parser Word8
word8 Word8
09) (Permutation (Parser ByteString) SAM_V1_6_Program
 -> Parser SAM_V1_6_Program)
-> Permutation (Parser ByteString) SAM_V1_6_Program
-> Parser SAM_V1_6_Program
forall a b. (a -> b) -> a -> b
$
          SAM_V1_6_Program_Record_Identifier
-> Maybe SAM_V1_6_Program_Name
-> Maybe SAM_V1_6_Program_Command_Line
-> Maybe SAM_V1_6_Program_Previous_PG_ID
-> Maybe SAM_V1_6_Program_Description
-> Maybe SAM_V1_6_Program_Version
-> SAM_V1_6_Program
SAM_V1_6_Program
            (SAM_V1_6_Program_Record_Identifier
 -> Maybe SAM_V1_6_Program_Name
 -> Maybe SAM_V1_6_Program_Command_Line
 -> Maybe SAM_V1_6_Program_Previous_PG_ID
 -> Maybe SAM_V1_6_Program_Description
 -> Maybe SAM_V1_6_Program_Version
 -> SAM_V1_6_Program)
-> Permutation
     (Parser ByteString) SAM_V1_6_Program_Record_Identifier
-> Permutation
     (Parser ByteString)
     (Maybe SAM_V1_6_Program_Name
      -> Maybe SAM_V1_6_Program_Command_Line
      -> Maybe SAM_V1_6_Program_Previous_PG_ID
      -> Maybe SAM_V1_6_Program_Description
      -> Maybe SAM_V1_6_Program_Version
      -> SAM_V1_6_Program)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Record_Identifier
-> Permutation
     (Parser ByteString) SAM_V1_6_Program_Record_Identifier
forall (m :: * -> *) a. Alternative m => m a -> Permutation m a
toPermutation Parser ByteString SAM_V1_6_Program_Record_Identifier
parse_SAM_V1_6_Program_ID
            Permutation
  (Parser ByteString)
  (Maybe SAM_V1_6_Program_Name
   -> Maybe SAM_V1_6_Program_Command_Line
   -> Maybe SAM_V1_6_Program_Previous_PG_ID
   -> Maybe SAM_V1_6_Program_Description
   -> Maybe SAM_V1_6_Program_Version
   -> SAM_V1_6_Program)
-> Permutation (Parser ByteString) (Maybe SAM_V1_6_Program_Name)
-> Permutation
     (Parser ByteString)
     (Maybe SAM_V1_6_Program_Command_Line
      -> Maybe SAM_V1_6_Program_Previous_PG_ID
      -> Maybe SAM_V1_6_Program_Description
      -> Maybe SAM_V1_6_Program_Version
      -> SAM_V1_6_Program)
forall a b.
Permutation (Parser ByteString) (a -> b)
-> Permutation (Parser ByteString) a
-> Permutation (Parser ByteString) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SAM_V1_6_Program_Name
-> Parser ByteString (Maybe SAM_V1_6_Program_Name)
-> Permutation (Parser ByteString) (Maybe SAM_V1_6_Program_Name)
forall (m :: * -> *) a.
Alternative m =>
a -> m a -> Permutation m a
toPermutationWithDefault Maybe SAM_V1_6_Program_Name
forall a. Maybe a
Nothing
                                         (SAM_V1_6_Program_Name -> Maybe SAM_V1_6_Program_Name
forall a. a -> Maybe a
Just (SAM_V1_6_Program_Name -> Maybe SAM_V1_6_Program_Name)
-> Parser ByteString SAM_V1_6_Program_Name
-> Parser ByteString (Maybe SAM_V1_6_Program_Name)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Name
parse_SAM_V1_6_Program_PN)
            Permutation
  (Parser ByteString)
  (Maybe SAM_V1_6_Program_Command_Line
   -> Maybe SAM_V1_6_Program_Previous_PG_ID
   -> Maybe SAM_V1_6_Program_Description
   -> Maybe SAM_V1_6_Program_Version
   -> SAM_V1_6_Program)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Command_Line)
-> Permutation
     (Parser ByteString)
     (Maybe SAM_V1_6_Program_Previous_PG_ID
      -> Maybe SAM_V1_6_Program_Description
      -> Maybe SAM_V1_6_Program_Version
      -> SAM_V1_6_Program)
forall a b.
Permutation (Parser ByteString) (a -> b)
-> Permutation (Parser ByteString) a
-> Permutation (Parser ByteString) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SAM_V1_6_Program_Command_Line
-> Parser ByteString (Maybe SAM_V1_6_Program_Command_Line)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Command_Line)
forall (m :: * -> *) a.
Alternative m =>
a -> m a -> Permutation m a
toPermutationWithDefault Maybe SAM_V1_6_Program_Command_Line
forall a. Maybe a
Nothing
                                         (SAM_V1_6_Program_Command_Line
-> Maybe SAM_V1_6_Program_Command_Line
forall a. a -> Maybe a
Just (SAM_V1_6_Program_Command_Line
 -> Maybe SAM_V1_6_Program_Command_Line)
-> Parser ByteString SAM_V1_6_Program_Command_Line
-> Parser ByteString (Maybe SAM_V1_6_Program_Command_Line)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Command_Line
parse_SAM_V1_6_Program_CL)
            Permutation
  (Parser ByteString)
  (Maybe SAM_V1_6_Program_Previous_PG_ID
   -> Maybe SAM_V1_6_Program_Description
   -> Maybe SAM_V1_6_Program_Version
   -> SAM_V1_6_Program)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Previous_PG_ID)
-> Permutation
     (Parser ByteString)
     (Maybe SAM_V1_6_Program_Description
      -> Maybe SAM_V1_6_Program_Version -> SAM_V1_6_Program)
forall a b.
Permutation (Parser ByteString) (a -> b)
-> Permutation (Parser ByteString) a
-> Permutation (Parser ByteString) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SAM_V1_6_Program_Previous_PG_ID
-> Parser ByteString (Maybe SAM_V1_6_Program_Previous_PG_ID)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Previous_PG_ID)
forall (m :: * -> *) a.
Alternative m =>
a -> m a -> Permutation m a
toPermutationWithDefault Maybe SAM_V1_6_Program_Previous_PG_ID
forall a. Maybe a
Nothing
                                         (SAM_V1_6_Program_Previous_PG_ID
-> Maybe SAM_V1_6_Program_Previous_PG_ID
forall a. a -> Maybe a
Just (SAM_V1_6_Program_Previous_PG_ID
 -> Maybe SAM_V1_6_Program_Previous_PG_ID)
-> Parser ByteString SAM_V1_6_Program_Previous_PG_ID
-> Parser ByteString (Maybe SAM_V1_6_Program_Previous_PG_ID)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Previous_PG_ID
parse_SAM_V1_6_Program_PP)
            Permutation
  (Parser ByteString)
  (Maybe SAM_V1_6_Program_Description
   -> Maybe SAM_V1_6_Program_Version -> SAM_V1_6_Program)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Description)
-> Permutation
     (Parser ByteString)
     (Maybe SAM_V1_6_Program_Version -> SAM_V1_6_Program)
forall a b.
Permutation (Parser ByteString) (a -> b)
-> Permutation (Parser ByteString) a
-> Permutation (Parser ByteString) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SAM_V1_6_Program_Description
-> Parser ByteString (Maybe SAM_V1_6_Program_Description)
-> Permutation
     (Parser ByteString) (Maybe SAM_V1_6_Program_Description)
forall (m :: * -> *) a.
Alternative m =>
a -> m a -> Permutation m a
toPermutationWithDefault Maybe SAM_V1_6_Program_Description
forall a. Maybe a
Nothing
                                         (SAM_V1_6_Program_Description -> Maybe SAM_V1_6_Program_Description
forall a. a -> Maybe a
Just (SAM_V1_6_Program_Description
 -> Maybe SAM_V1_6_Program_Description)
-> Parser ByteString SAM_V1_6_Program_Description
-> Parser ByteString (Maybe SAM_V1_6_Program_Description)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Description
parse_SAM_V1_6_Program_DS)
            Permutation
  (Parser ByteString)
  (Maybe SAM_V1_6_Program_Version -> SAM_V1_6_Program)
-> Permutation (Parser ByteString) (Maybe SAM_V1_6_Program_Version)
-> Permutation (Parser ByteString) SAM_V1_6_Program
forall a b.
Permutation (Parser ByteString) (a -> b)
-> Permutation (Parser ByteString) a
-> Permutation (Parser ByteString) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SAM_V1_6_Program_Version
-> Parser ByteString (Maybe SAM_V1_6_Program_Version)
-> Permutation (Parser ByteString) (Maybe SAM_V1_6_Program_Version)
forall (m :: * -> *) a.
Alternative m =>
a -> m a -> Permutation m a
toPermutationWithDefault Maybe SAM_V1_6_Program_Version
forall a. Maybe a
Nothing
                                         (SAM_V1_6_Program_Version -> Maybe SAM_V1_6_Program_Version
forall a. a -> Maybe a
Just (SAM_V1_6_Program_Version -> Maybe SAM_V1_6_Program_Version)
-> Parser ByteString SAM_V1_6_Program_Version
-> Parser ByteString (Maybe SAM_V1_6_Program_Version)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString SAM_V1_6_Program_Version
parse_SAM_V1_6_Program_VN)
  ()
_ <- Parser ByteString ()
endOfLine
  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
pg