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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Identity a -> a
Identity.runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
  ByteString
s1 <- forall (m :: * -> *) s. Applicative m => Get s m s
Get.get
  let (ByteString
x, ByteString
s2) = Int -> ByteString -> (ByteString, ByteString)
ByteString.splitAt Int
n ByteString
s1
  if ByteString -> Int
ByteString.length ByteString
x forall a. Eq a => a -> a -> Bool
== Int
n
    then do
      forall (m :: * -> *) s. Applicative m => s -> Get s m ()
Get.put ByteString
s2
      forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
x
    else forall e a. Exception e => e -> ByteGet a
throw NotEnoughInput
NotEnoughInput.NotEnoughInput

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

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

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

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

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

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

word32 :: ByteGet Word.Word32
word32 :: ByteGet Word32
word32 = do
  ByteString
x <- Int -> ByteGet ByteString
byteString Int
4
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
    forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
0) Int
0
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
1) Int
8
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
2) Int
16
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
3) Int
24

word64 :: ByteGet Word.Word64
word64 :: ByteGet Word64
word64 = do
  ByteString
x <- Int -> ByteGet ByteString
byteString Int
8
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
    forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
0) Int
0
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
1) Int
8
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
2) Int
16
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
3) Int
24
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
4) Int
32
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
5) Int
40
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
6) Int
48
      forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
Bits.shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString.index ByteString
x Int
7) Int
56

throw :: (Exception.Exception e) => e -> ByteGet a
throw :: forall e a. Exception e => e -> ByteGet a
throw = 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 = 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 = forall (m :: * -> *) s a.
Functor m =>
String -> Get s m a -> Get s m a
Get.label