{-# 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           #-}
module Data.SAM.Version1_6.Read.Parser.Header.RG.FO ( 
                                                      parse_SAM_V1_6_Read_Group_FO
                                                    ) where
import Data.SAM.Version1_6.Header
import Data.SAM.Version1_6.Read.Error
import Data.Attoparsec.ByteString.Char8 (isEndOfLine)
import Data.Attoparsec.ByteString.Lazy as DABL
import Text.Regex.PCRE.Heavy
parse_SAM_V1_6_Read_Group_FO :: Parser SAM_V1_6_Read_Group_Flow_Order 
parse_SAM_V1_6_Read_Group_FO :: Parser SAM_V1_6_Read_Group_Flow_Order
parse_SAM_V1_6_Read_Group_FO = do
  ()
_ <- do ByteString
rgheaderflowordertagp <- (Word8 -> Bool) -> Parser ByteString
DABL.takeTill (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
58)
          
          case (ByteString
rgheaderflowordertagp ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|[F][O]|]) 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_Read_Group_Flow_Order_Incorrect_Format
            Bool
True  -> 
                     () -> Parser ByteString ()
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  Word8
_ <- Word8 -> Parser Word8
word8 Word8
58
  ByteString
rgheaderflowordervalue <- do ByteString
rgheaderflowordervaluep <- (Word8 -> Bool) -> Parser ByteString
DABL.takeTill (\Word8
x -> Word8
x Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
09 Bool -> Bool -> Bool
|| Word8 -> Bool
isEndOfLine Word8
x)
                               
                               case (ByteString
rgheaderflowordervaluep ByteString -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ [re|\*|[ACMGRSVTWYHKDBN]+|]) 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_Read_Group_Flow_Order_Incorrect_Format
                                 Bool
True  -> 
                                          ByteString -> Parser ByteString
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
rgheaderflowordervaluep
  SAM_V1_6_Read_Group_Flow_Order
-> Parser SAM_V1_6_Read_Group_Flow_Order
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return SAM_V1_6_Read_Group_Flow_Order { sam_v1_6_read_group_flow_order_value :: ByteString
sam_v1_6_read_group_flow_order_value = ByteString
rgheaderflowordervalue
                                        }