{-# language BangPatterns #-}
{-# language BinaryLiterals #-}
{-# language DataKinds #-}
{-# language DeriveFunctor #-}
{-# language DerivingStrategies #-}
{-# language GADTSyntax #-}
{-# language KindSignatures #-}
{-# language LambdaCase #-}
{-# language MagicHash #-}
{-# language MultiWayIf #-}
{-# language PolyKinds #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language StandaloneDeriving #-}
{-# language TypeApplications #-}
{-# language UnboxedSums #-}
{-# language UnboxedTuples #-}
module Data.Bytes.Parser.LittleEndian
(
word8
, word16
, word32
, word64
, word128
, int8
, int16
, int32
, int64
, word16Array
, word32Array
, word64Array
, word128Array
, int64Array
) where
import Prelude hiding (length,any,fail,takeWhile)
import Control.Applicative (liftA2)
import Data.Bits ((.|.),unsafeShiftL)
import Data.Primitive (ByteArray(..),PrimArray(..))
import Data.Bytes.Types (Bytes(..))
import Data.Bytes.Parser.Internal (Parser,uneffectful)
import Data.Bytes.Parser.Internal (InternalResult(..))
import Data.Bytes.Parser.Internal (swapArray16,swapArray32)
import Data.Bytes.Parser.Internal (swapArray64,swapArray128)
import Data.Word (Word8,Word16,Word32,Word64)
import Data.Int (Int8,Int16,Int32,Int64)
import Data.WideWord (Word128(Word128))
import GHC.ByteOrder (ByteOrder(LittleEndian,BigEndian),targetByteOrder)
import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Parser as P
import qualified Data.Primitive as PM
word8 :: e -> Parser e s Word8
word8 = P.any
word16Array ::
e
-> Int
-> Parser e s (PrimArray Word16)
word16Array e !n = case targetByteOrder of
LittleEndian -> fmap (asWord16s . Bytes.toByteArrayClone) (P.take e (n * 2))
BigEndian -> do
bs <- P.take e (n * 2)
let r = swapArray16 bs
pure (asWord16s r)
word32Array ::
e
-> Int
-> Parser e s (PrimArray Word32)
word32Array e !n = case targetByteOrder of
LittleEndian -> fmap (asWord32s . Bytes.toByteArrayClone) (P.take e (n * 4))
BigEndian -> do
bs <- P.take e (n * 4)
let r = swapArray32 bs
pure (asWord32s r)
word64Array ::
e
-> Int
-> Parser e s (PrimArray Word64)
word64Array e !n = case targetByteOrder of
LittleEndian -> fmap (asWord64s . Bytes.toByteArrayClone) (P.take e (n * 8))
BigEndian -> do
bs <- P.take e (n * 8)
let r = swapArray64 bs
pure (asWord64s r)
word128Array ::
e
-> Int
-> Parser e s (PrimArray Word128)
word128Array e !n = case targetByteOrder of
LittleEndian -> fmap (asWord128s . Bytes.toByteArrayClone) (P.take e (n * 16))
BigEndian -> do
bs <- P.take e (n * 16)
let r = swapArray128 bs
pure (asWord128s r)
int64Array ::
e
-> Int
-> Parser e s (PrimArray Int64)
int64Array e !n = do
PrimArray x <- word64Array e n
pure (PrimArray x)
asWord16s :: ByteArray -> PrimArray Word16
asWord16s (ByteArray x) = PrimArray x
asWord32s :: ByteArray -> PrimArray Word32
asWord32s (ByteArray x) = PrimArray x
asWord64s :: ByteArray -> PrimArray Word64
asWord64s (ByteArray x) = PrimArray x
asWord128s :: ByteArray -> PrimArray Word128
asWord128s (ByteArray x) = PrimArray x
word16 :: e -> Parser e s Word16
word16 e = uneffectful $ \chunk -> if length chunk >= 2
then
let wa = PM.indexByteArray (array chunk) (offset chunk) :: Word8
wb = PM.indexByteArray (array chunk) (offset chunk + 1) :: Word8
in InternalSuccess
(fromIntegral @Word @Word16 (unsafeShiftL (fromIntegral wb) 8 .|. fromIntegral wa))
(offset chunk + 2) (length chunk - 2)
else InternalFailure e
word32 :: e -> Parser e s Word32
word32 e = uneffectful $ \chunk -> if length chunk >= 4
then
let wa = PM.indexByteArray (array chunk) (offset chunk) :: Word8
wb = PM.indexByteArray (array chunk) (offset chunk + 1) :: Word8
wc = PM.indexByteArray (array chunk) (offset chunk + 2) :: Word8
wd = PM.indexByteArray (array chunk) (offset chunk + 3) :: Word8
in InternalSuccess
(fromIntegral @Word @Word32
( unsafeShiftL (fromIntegral wd) 24 .|.
unsafeShiftL (fromIntegral wc) 16 .|.
unsafeShiftL (fromIntegral wb) 8 .|.
fromIntegral wa
)
)
(offset chunk + 4) (length chunk - 4)
else InternalFailure e
word64 :: e -> Parser e s Word64
word64 e = uneffectful $ \chunk -> if length chunk >= 8
then
let wa = PM.indexByteArray (array chunk) (offset chunk) :: Word8
wb = PM.indexByteArray (array chunk) (offset chunk + 1) :: Word8
wc = PM.indexByteArray (array chunk) (offset chunk + 2) :: Word8
wd = PM.indexByteArray (array chunk) (offset chunk + 3) :: Word8
we = PM.indexByteArray (array chunk) (offset chunk + 4) :: Word8
wf = PM.indexByteArray (array chunk) (offset chunk + 5) :: Word8
wg = PM.indexByteArray (array chunk) (offset chunk + 6) :: Word8
wh = PM.indexByteArray (array chunk) (offset chunk + 7) :: Word8
in InternalSuccess
( unsafeShiftL (fromIntegral wh) 56 .|.
unsafeShiftL (fromIntegral wg) 48 .|.
unsafeShiftL (fromIntegral wf) 40 .|.
unsafeShiftL (fromIntegral we) 32 .|.
unsafeShiftL (fromIntegral wd) 24 .|.
unsafeShiftL (fromIntegral wc) 16 .|.
unsafeShiftL (fromIntegral wb) 8 .|.
fromIntegral wa
)
(offset chunk + 8) (length chunk - 8)
else InternalFailure e
word128 :: e -> Parser e s Word128
word128 e = liftA2 (flip Word128) (word64 e) (word64 e)
int8 :: e -> Parser e s Int8
int8 = fmap fromIntegral . word8
int16 :: e -> Parser e s Int16
int16 = fmap fromIntegral . word16
int32 :: e -> Parser e s Int32
int32 = fmap fromIntegral . word32
int64 :: e -> Parser e s Int64
int64 = fmap fromIntegral . word64