{-# 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.Alignment.HOPT (
parse_SAM_V1_6_Alignment_HOPT
) where
import Data.SAM.Version1_6.Read.Error
import Data.Attoparsec.ByteString.Lazy as DABL
import qualified Data.ByteString as DB
import Data.Sequence as DSeq
import Data.Word
import Text.Regex.PCRE.Heavy
parse_SAM_V1_6_Alignment_HOPT :: Parser (Seq Word8)
parse_SAM_V1_6_Alignment_HOPT :: Parser (Seq Word8)
parse_SAM_V1_6_Alignment_HOPT = do
ByteString
_ <- do ByteString
alignmenthoptfieldtagp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
case (ByteString
alignmenthoptfieldtagp 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_HOPT_Tag_Incorrect_Format
Bool
True ->
ByteString -> Parser ByteString ByteString
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
alignmenthoptfieldtagp
Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
ByteString
_ <- do ByteString
alignmenthoptfieldtypep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
case (ByteString
alignmenthoptfieldtypep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[H]|]) 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_HOPT_Type_Incorrect_Format
Bool
True ->
ByteString -> Parser ByteString ByteString
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
alignmenthoptfieldtypep
Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
Seq Word8
alignmenthoptfieldvalue <- do ByteString
alignmenthoptfieldvaluep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09)
case (ByteString
alignmenthoptfieldvaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|([0-9A-F][0-9A-F])*|]) of
Bool
False -> String -> Parser (Seq Word8)
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (Seq Word8)) -> String -> Parser (Seq Word8)
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_HOPT_Value_Incorrect_Format
Bool
True ->
Seq Word8 -> Parser (Seq Word8)
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq Word8 -> Parser (Seq Word8))
-> Seq Word8 -> Parser (Seq Word8)
forall a b. (a -> b) -> a -> b
$ [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
alignmenthoptfieldvaluep
Seq Word8 -> Parser (Seq Word8)
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return Seq Word8
alignmenthoptfieldvalue