{-# 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.PG.DS (
parse_SAM_V1_6_SAM_V1_6_Program_DS
) 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
parse_SAM_V1_6_SAM_V1_6_Program_DS :: Parser SAM_V1_6_Program_Description
parse_SAM_V1_6_SAM_V1_6_Program_DS :: Parser SAM_V1_6_Program_Description
parse_SAM_V1_6_SAM_V1_6_Program_DS = do
ByteString
pgheaderdescriptiontag <- do ByteString
pgheaderdescriptiontagp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
case (ByteString
pgheaderdescriptiontagp ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[D][S]|]) 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_Description_Incorrect_Format
Bool
True ->
ByteString -> Parser ByteString ByteString
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
pgheaderdescriptiontagp
Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
ByteString
pgheaderdescriptionvalue <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09)
SAM_V1_6_Program_Description -> Parser SAM_V1_6_Program_Description
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return SAM_V1_6_Program_Description { sam_v1_6_program_description_tag :: Seq Word8
sam_v1_6_program_description_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
pgheaderdescriptiontag
, sam_v1_6_program_description_value :: ByteString
sam_v1_6_program_description_value = ByteString
pgheaderdescriptionvalue
}