{-# 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.FOPT (
parse_SAM_V1_6_Alignment_FOPT
) where
import Data.SAM.Version1_6.Read.Error
import Data.Attoparsec.ByteString.Lazy as DABL
import qualified Data.ByteString.Char8 as DBC8
import Text.Regex.PCRE.Heavy
parse_SAM_V1_6_Alignment_FOPT :: Parser Float
parse_SAM_V1_6_Alignment_FOPT :: Parser Float
parse_SAM_V1_6_Alignment_FOPT = do
ByteString
_ <- do ByteString
alignmentfoptfieldtagp <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
case (ByteString
alignmentfoptfieldtagp 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_FOPT_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
alignmentfoptfieldtagp
Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
ByteString
_ <- do ByteString
alignmentfoptfieldtypep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
case (ByteString
alignmentfoptfieldtypep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[f]|]) 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_FOPT_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
alignmentfoptfieldtypep
Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
Float
alignmentfoptfieldvalue <- do ByteString
alignmentfoptfieldvaluep <- (Word8 -> Bool) -> Parser ByteString ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09)
case (ByteString
alignmentfoptfieldvaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[-+]?[0-9]*\.?[0-9]+([eE][-+]?[0-9]+)?|]) of
Bool
False -> String -> Parser Float
forall a. String -> Parser ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Float) -> String -> Parser Float
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_FOPT_Value_Incorrect_Format
Bool
True ->
case (ByteString -> Maybe (Integer, ByteString)
DBC8.readInteger ByteString
alignmentfoptfieldvaluep) of
Maybe (Integer, ByteString)
Nothing -> Float -> Parser Float
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Float
1)
Just (Integer
alignmentfoptfieldvalueinteger,ByteString
_) -> Float -> Parser Float
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float -> Parser Float) -> Float -> Parser Float
forall a b. (a -> b) -> a -> b
$ (Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
alignmentfoptfieldvalueinteger :: Float)
Float -> Parser Float
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
alignmentfoptfieldvalue