{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Data.BAM.Version1_6.Read.Parser.BAM.ReferenceInformation.Base (
parse_BAM_V1_6_BAM_Reference_Information
) where
import Data.BAM.Version1_6.BAM.ReferenceInformation
import Data.BAM.Version1_6.Internal
import Data.Attoparsec.ByteString.Lazy as DABL
import Data.ByteString as DB
parse_BAM_V1_6_BAM_Reference_Information :: Parser BAM_V1_6_BAM_Reference_Information
parse_BAM_V1_6_BAM_Reference_Information :: Parser BAM_V1_6_BAM_Reference_Information
parse_BAM_V1_6_BAM_Reference_Information = do
ByteString
l_name <-
Int -> Parser ByteString
DABL.take Int
4
ByteString
name <-
Int -> Parser ByteString
DABL.take (Int -> Parser ByteString) -> Int -> Parser ByteString
forall a b. (a -> b) -> a -> b
$
Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Word32 -> Int
forall a b. (a -> b) -> a -> b
$
[Word8] -> Word32
word8sToWord32LE ([Word8] -> Word32) -> [Word8] -> Word32
forall a b. (a -> b) -> a -> b
$
ByteString -> [Word8]
DB.unpack ByteString
l_name
ByteString
l_ref <-
Int -> Parser ByteString
DABL.take Int
4
BAM_V1_6_BAM_Reference_Information
-> Parser BAM_V1_6_BAM_Reference_Information
forall a. a -> Parser ByteString a
forall (m :: * -> *) a. Monad m => a -> m a
return BAM_V1_6_BAM_Reference_Information
{ bam_v1_6_bam_reference_information_l_name :: Word32
bam_v1_6_bam_reference_information_l_name = [Word8] -> Word32
word8sToWord32LE ([Word8] -> Word32) -> [Word8] -> Word32
forall a b. (a -> b) -> a -> b
$
ByteString -> [Word8]
DB.unpack ByteString
l_name
, bam_v1_6_bam_reference_information_name :: ByteString
bam_v1_6_bam_reference_information_name = ByteString
name
, bam_v1_6_bam_reference_information_l_ref :: Word32
bam_v1_6_bam_reference_information_l_ref = [Word8] -> Word32
word8sToWord32LE ([Word8] -> Word32) -> [Word8] -> Word32
forall a b. (a -> b) -> a -> b
$
ByteString -> [Word8]
DB.unpack ByteString
l_ref
}