{-# LANGUAGE FlexibleContexts            #-}
{-# LANGUAGE FlexibleInstances           #-}
{-# LANGUAGE MultiParamTypeClasses       #-}
{-# LANGUAGE TypeFamilies                #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}

-- |
-- Module      :  Data.BAM.Version1_6.Read.Parser.BAM.ReferenceInformation.Base
-- Copyright   :  (c) Matthew Mosior 2024
-- License     :  BSD-style
-- Maintainer  :  mattm.github@gmail.com
-- Portability :  portable
--
-- = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this library are expected to track development
-- closely.
--
-- All credit goes to the author(s)/maintainer(s) of the
-- [containers](https://hackage.haskell.org/package/containers) library
-- for the above warning text.
--
-- = Description
--
-- This library enables the decoding/encoding of SAM, BAM and CRAM file formats.

module Data.BAM.Version1_6.Read.Parser.BAM.ReferenceInformation.Base ( -- * BAM_V1_6_BAM parser - reference information section
                                                                       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

-- | @"BAM_V1_6_BAM_Reference_Information"@ parser.
--
-- Defines a parser for the alignment section of the BAM v1.6 file format.
--
-- See the [SAM v1.6](http://samtools.github.io/hts-specs/SAMv1.pdf) specification documentation.
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
           }