module Rattletrap.ByteGet where

import qualified Control.Exception as Exception
import qualified Data.Bits as Bits
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as LazyByteString
import qualified Data.Functor.Identity as Identity
import qualified Data.Int as Int
import qualified Data.Word as Word
import qualified GHC.Float as Float
import qualified Rattletrap.Exception.NotEnoughInput as NotEnoughInput
import qualified Rattletrap.Get as Get

type ByteGet = Get.Get ByteString.ByteString Identity.Identity

run ::
  ByteGet a ->
  ByteString.ByteString ->
  Either ([String], Exception.SomeException) a
run :: forall a.
ByteGet a -> ByteString -> Either ([String], SomeException) a
run ByteGet a
g = ((ByteString, a) -> a)
-> Either ([String], SomeException) (ByteString, a)
-> Either ([String], SomeException) a
forall a b.
(a -> b)
-> Either ([String], SomeException) a
-> Either ([String], SomeException) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString, a) -> a
forall a b. (a, b) -> b
snd (Either ([String], SomeException) (ByteString, a)
 -> Either ([String], SomeException) a)
-> (ByteString -> Either ([String], SomeException) (ByteString, a))
-> ByteString
-> Either ([String], SomeException) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (Either ([String], SomeException) (ByteString, a))
-> Either ([String], SomeException) (ByteString, a)
forall a. Identity a -> a
Identity.runIdentity (Identity (Either ([String], SomeException) (ByteString, a))
 -> Either ([String], SomeException) (ByteString, a))
-> (ByteString
    -> Identity (Either ([String], SomeException) (ByteString, a)))
-> ByteString
-> Either ([String], SomeException) (ByteString, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteGet a
-> ByteString
-> Identity (Either ([String], SomeException) (ByteString, a))
forall s (m :: * -> *) a.
Get s m a -> s -> m (Either ([String], SomeException) (s, a))
Get.run ByteGet a
g

byteString :: Int -> ByteGet ByteString.ByteString
byteString :: Int -> ByteGet ByteString
byteString Int
n = do
  s1 <- ByteGet ByteString
forall (m :: * -> *) s. Applicative m => Get s m s
Get.get
  let (x, s2) = ByteString.splitAt n s1
  if ByteString.length x == n
    then do
      Get.put s2
      pure x
    else throw NotEnoughInput.NotEnoughInput

float :: ByteGet Float
float :: ByteGet Float
float = (Word32 -> Float)
-> Get ByteString Identity Word32 -> ByteGet Float
forall a b.
(a -> b) -> Get ByteString Identity a -> Get ByteString Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Float
Float.castWord32ToFloat Get ByteString Identity Word32
word32

int8 :: ByteGet Int.Int8
int8 :: ByteGet Int8
int8 = (Word8 -> Int8) -> Get ByteString Identity Word8 -> ByteGet Int8
forall a b.
(a -> b) -> Get ByteString Identity a -> Get ByteString Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Get ByteString Identity Word8
word8

int32 :: ByteGet Int.Int32
int32 :: ByteGet Int32
int32 = (Word32 -> Int32)
-> Get ByteString Identity Word32 -> ByteGet Int32
forall a b.
(a -> b) -> Get ByteString Identity a -> Get ByteString Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Get ByteString Identity Word32
word32

int64 :: ByteGet Int.Int64
int64 :: ByteGet Int64
int64 = (Word64 -> Int64)
-> Get ByteString Identity Word64 -> ByteGet Int64
forall a b.
(a -> b) -> Get ByteString Identity a -> Get ByteString Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Get ByteString Identity Word64
word64

remaining :: ByteGet LazyByteString.ByteString
remaining :: ByteGet ByteString
remaining = do
  x <- ByteGet ByteString
forall (m :: * -> *) s. Applicative m => Get s m s
Get.get
  Get.put ByteString.empty
  pure $ LazyByteString.fromStrict x

word8 :: ByteGet Word.Word8
word8 :: Get ByteString Identity Word8
word8 = (ByteString -> Word8)
-> ByteGet ByteString -> Get ByteString Identity Word8
forall a b.
(a -> b) -> Get ByteString Identity a -> Get ByteString Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HasCallStack => ByteString -> Word8
ByteString -> Word8
ByteString.head (ByteGet ByteString -> Get ByteString Identity Word8)
-> ByteGet ByteString -> Get ByteString Identity Word8
forall a b. (a -> b) -> a -> b
$ Int -> ByteGet ByteString
byteString Int
1

word32 :: ByteGet Word.Word32
word32 :: Get ByteString Identity Word32
word32 = do
  x <- Int -> ByteGet ByteString
byteString Int
4
  pure $
    Bits.shiftL (fromIntegral $ ByteString.index x 0) 0
      + Bits.shiftL (fromIntegral $ ByteString.index x 1) 8
      + Bits.shiftL (fromIntegral $ ByteString.index x 2) 16
      + Bits.shiftL (fromIntegral $ ByteString.index x 3) 24

word64 :: ByteGet Word.Word64
word64 :: Get ByteString Identity Word64
word64 = do
  x <- Int -> ByteGet ByteString
byteString Int
8
  pure $
    Bits.shiftL (fromIntegral $ ByteString.index x 0) 0
      + Bits.shiftL (fromIntegral $ ByteString.index x 1) 8
      + Bits.shiftL (fromIntegral $ ByteString.index x 2) 16
      + Bits.shiftL (fromIntegral $ ByteString.index x 3) 24
      + Bits.shiftL (fromIntegral $ ByteString.index x 4) 32
      + Bits.shiftL (fromIntegral $ ByteString.index x 5) 40
      + Bits.shiftL (fromIntegral $ ByteString.index x 6) 48
      + Bits.shiftL (fromIntegral $ ByteString.index x 7) 56

throw :: (Exception.Exception e) => e -> ByteGet a
throw :: forall e a. Exception e => e -> ByteGet a
throw = e -> Get ByteString Identity a
forall e (m :: * -> *) s a.
(Exception e, Applicative m) =>
e -> Get s m a
Get.throw

embed :: ByteGet a -> ByteString.ByteString -> ByteGet a
embed :: forall a. ByteGet a -> ByteString -> ByteGet a
embed = Get ByteString Identity a
-> ByteString -> Get ByteString Identity a
forall (m :: * -> *) s a t. Monad m => Get s m a -> s -> Get t m a
Get.embed

label :: String -> ByteGet a -> ByteGet a
label :: forall a. String -> ByteGet a -> ByteGet a
label = String -> Get ByteString Identity a -> Get ByteString Identity a
forall (m :: * -> *) s a.
Functor m =>
String -> Get s m a -> Get s m a
Get.label