{-# LANGUAGE CPP #-}
#include <MachDeps.h>
module Data.Binary.ZLEB128
( ZLEB128(..)
, putInteger
, putInt64
, putInt32
, putInt16
, putInt8
, putInt
, putNatural
, putWord64
, putWord32
, putWord16
, putWord8
, putWord
, getInteger
, getInt64
, getInt32
, getInt16
, getInt8
, getInt
, getNatural
, getWord64
, getWord32
, getWord16
, getWord8
, getWord
)
where
import Data.Binary qualified as Bin
import Data.Binary.Get qualified as Bin
import Data.Bits
import GHC.Num.BigNat
import GHC.Num.Integer
import GHC.Num.Natural
import GHC.Int
import GHC.Word
import GHC.Exts
import Data.Binary.ULEB128 qualified as U
newtype ZLEB128 x = ZLEB128 x
instance Bin.Binary (ZLEB128 Integer) where
put :: ZLEB128 Integer -> Put
put = (Integer -> Put) -> ZLEB128 Integer -> Put
forall a b. Coercible a b => a -> b
coerce Integer -> Put
putInteger
{-# INLINE put #-}
get :: Get (ZLEB128 Integer)
get = Get Integer -> Get (ZLEB128 Integer)
forall a b. Coercible a b => a -> b
coerce (Int -> Get Integer
getInteger Int
1024)
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Natural) where
put :: ZLEB128 Natural -> Put
put = (Natural -> Put) -> ZLEB128 Natural -> Put
forall a b. Coercible a b => a -> b
coerce Natural -> Put
putNatural
{-# INLINE put #-}
get :: Get (ZLEB128 Natural)
get = Get Natural -> Get (ZLEB128 Natural)
forall a b. Coercible a b => a -> b
coerce (Int -> Get Natural
getNatural Int
1024)
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Int) where
put :: ZLEB128 Int -> Put
put = (Int -> Put) -> ZLEB128 Int -> Put
forall a b. Coercible a b => a -> b
coerce Int -> Put
putInt
{-# INLINE put #-}
get :: Get (ZLEB128 Int)
get = Get Int -> Get (ZLEB128 Int)
forall a b. Coercible a b => a -> b
coerce Get Int
getInt
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Word) where
put :: ZLEB128 Word -> Put
put = (Word -> Put) -> ZLEB128 Word -> Put
forall a b. Coercible a b => a -> b
coerce Word -> Put
putWord
{-# INLINE put #-}
get :: Get (ZLEB128 Word)
get = Get Word -> Get (ZLEB128 Word)
forall a b. Coercible a b => a -> b
coerce Get Word
getWord
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Int8) where
put :: ZLEB128 Int8 -> Put
put = (Int8 -> Put) -> ZLEB128 Int8 -> Put
forall a b. Coercible a b => a -> b
coerce Int8 -> Put
putInt8
{-# INLINE put #-}
get :: Get (ZLEB128 Int8)
get = Get Int8 -> Get (ZLEB128 Int8)
forall a b. Coercible a b => a -> b
coerce Get Int8
getInt8
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Word8) where
put :: ZLEB128 Word8 -> Put
put = (Word8 -> Put) -> ZLEB128 Word8 -> Put
forall a b. Coercible a b => a -> b
coerce Word8 -> Put
putWord8
{-# INLINE put #-}
get :: Get (ZLEB128 Word8)
get = Get Word8 -> Get (ZLEB128 Word8)
forall a b. Coercible a b => a -> b
coerce Get Word8
getWord8
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Int16) where
put :: ZLEB128 Int16 -> Put
put = (Int16 -> Put) -> ZLEB128 Int16 -> Put
forall a b. Coercible a b => a -> b
coerce Int16 -> Put
putInt16
{-# INLINE put #-}
get :: Get (ZLEB128 Int16)
get = Get Int16 -> Get (ZLEB128 Int16)
forall a b. Coercible a b => a -> b
coerce Get Int16
getInt16
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Word16) where
put :: ZLEB128 Word16 -> Put
put = (Word16 -> Put) -> ZLEB128 Word16 -> Put
forall a b. Coercible a b => a -> b
coerce Word16 -> Put
putWord16
{-# INLINE put #-}
get :: Get (ZLEB128 Word16)
get = Get Word16 -> Get (ZLEB128 Word16)
forall a b. Coercible a b => a -> b
coerce Get Word16
getWord16
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Int32) where
put :: ZLEB128 Int32 -> Put
put = (Int32 -> Put) -> ZLEB128 Int32 -> Put
forall a b. Coercible a b => a -> b
coerce Int32 -> Put
putInt32
{-# INLINE put #-}
get :: Get (ZLEB128 Int32)
get = Get Int32 -> Get (ZLEB128 Int32)
forall a b. Coercible a b => a -> b
coerce Get Int32
getInt32
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Word32) where
put :: ZLEB128 Word32 -> Put
put = (Word32 -> Put) -> ZLEB128 Word32 -> Put
forall a b. Coercible a b => a -> b
coerce Word32 -> Put
putWord32
{-# INLINE put #-}
get :: Get (ZLEB128 Word32)
get = Get Word32 -> Get (ZLEB128 Word32)
forall a b. Coercible a b => a -> b
coerce Get Word32
getWord32
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Int64) where
put :: ZLEB128 Int64 -> Put
put = (Int64 -> Put) -> ZLEB128 Int64 -> Put
forall a b. Coercible a b => a -> b
coerce Int64 -> Put
putInt64
{-# INLINE put #-}
get :: Get (ZLEB128 Int64)
get = Get Int64 -> Get (ZLEB128 Int64)
forall a b. Coercible a b => a -> b
coerce Get Int64
getInt64
{-# INLINE get #-}
instance Bin.Binary (ZLEB128 Word64) where
put :: ZLEB128 Word64 -> Put
put = (Word64 -> Put) -> ZLEB128 Word64 -> Put
forall a b. Coercible a b => a -> b
coerce Word64 -> Put
putWord64
{-# INLINE put #-}
get :: Get (ZLEB128 Word64)
get = Get Word64 -> Get (ZLEB128 Word64)
forall a b. Coercible a b => a -> b
coerce Get Word64
getWord64
{-# INLINE get #-}
putInteger :: Integer -> Bin.Put
putInteger :: Integer -> Put
putInteger = \case
IS Int#
x | Word
y <- Int -> Word
zigZagInt (Int# -> Int
I# Int#
x) -> Word -> Put
U.putWord Word
y
IP ByteArray#
x -> Natural -> Put
U.putNatural (ByteArray# -> Natural
NB (ByteArray# -> Word# -> ByteArray#
bigNatShiftL# ByteArray#
x Word#
1##))
IN ByteArray#
x -> Natural -> Put
U.putNatural (ByteArray# -> Natural
NB (ByteArray# -> Word# -> ByteArray#
bigNatShiftL# ByteArray#
x Word#
1## ByteArray# -> Word# -> ByteArray#
`bigNatSubWordUnsafe#` Word#
1##))
{-# INLINE putInteger #-}
putNatural :: Natural -> Bin.Put
putNatural :: Natural -> Put
putNatural = \Natural
n -> Natural -> Put
U.putNatural (Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
unsafeShiftL Natural
n Int
1)
{-# INLINE putNatural #-}
putWord8 :: Word8 -> Bin.Put
putWord8 :: Word8 -> Put
putWord8 = Int16 -> Put
putInt16 (Int16 -> Put) -> (Word8 -> Int16) -> Word8 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE putWord8 #-}
putWord16 :: Word16 -> Bin.Put
putWord16 :: Word16 -> Put
putWord16 = Int32 -> Put
putInt32 (Int32 -> Put) -> (Word16 -> Int32) -> Word16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE putWord16 #-}
putWord32 :: Word32 -> Bin.Put
putWord32 :: Word32 -> Put
putWord32 = Int64 -> Put
putInt64 (Int64 -> Put) -> (Word32 -> Int64) -> Word32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE putWord32 #-}
putWord64 :: Word64 -> Bin.Put
putWord64 :: Word64 -> Put
putWord64 = Integer -> Put
putInteger (Integer -> Put) -> (Word64 -> Integer) -> Word64 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE putWord64 #-}
putWord :: Word -> Bin.Put
putWord :: Word -> Put
putWord = Integer -> Put
putInteger (Integer -> Put) -> (Word -> Integer) -> Word -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE putWord #-}
putInt8 :: Int8 -> Bin.Put
putInt8 :: Int8 -> Put
putInt8 = Word8 -> Put
U.putWord8 (Word8 -> Put) -> (Int8 -> Word8) -> Int8 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Word8
zigZagInt8
{-# INLINE putInt8 #-}
putInt16 :: Int16 -> Bin.Put
putInt16 :: Int16 -> Put
putInt16 = Word16 -> Put
U.putWord16 (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Word16
zigZagInt16
{-# INLINE putInt16 #-}
putInt32 :: Int32 -> Bin.Put
putInt32 :: Int32 -> Put
putInt32 = Word32 -> Put
U.putWord32 (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Word32
zigZagInt32
{-# INLINE putInt32 #-}
putInt64 :: Int64 -> Bin.Put
putInt64 :: Int64 -> Put
putInt64 = Word64 -> Put
U.putWord64 (Word64 -> Put) -> (Int64 -> Word64) -> Int64 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Word64
zigZagInt64
{-# INLINE putInt64 #-}
putInt :: Int -> Bin.Put
putInt :: Int -> Put
putInt = Word -> Put
U.putWord (Word -> Put) -> (Int -> Word) -> Int -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word
zigZagInt
{-# INLINE putInt #-}
getInteger
:: Int
-> Bin.Get Integer
getInteger :: Int -> Get Integer
getInteger = (Natural -> Integer) -> Get Natural -> Get Integer
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Natural -> Integer
zagZigInteger (Get Natural -> Get Integer)
-> (Int -> Get Natural) -> Int -> Get Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Get Natural
U.getNatural
{-# INLINE getInteger #-}
getNatural
:: Int
-> Bin.Get Natural
getNatural :: Int -> Get Natural
getNatural = \Int
m -> do
Integer
i <- Int -> Get Integer
getInteger Int
m
String -> Get Natural -> Get Natural
forall a. String -> Get a -> Get a
Bin.label String
"ZLEB128" (Get Natural -> Get Natural) -> Get Natural -> Get Natural
forall a b. (a -> b) -> a -> b
$ Integer -> Get Natural
forall (m :: * -> *). MonadFail m => Integer -> m Natural
naturalFromInteger Integer
i
{-# INLINE getNatural #-}
getBoundedIntegral
:: forall s u
. (Bits s, Integral s, Bits u, Integral u)
=> Bin.Get s
-> Bin.Get u
getBoundedIntegral :: forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral = \Get s
gs -> do
s
s <- Get s
gs
String -> Get u -> Get u
forall a. String -> Get a -> Get a
Bin.label String
"ZLEB128" (Get u -> Get u) -> Get u -> Get u
forall a b. (a -> b) -> a -> b
$ case s -> Maybe u
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
toIntegralSized s
s of
Just u
u -> u -> Get u
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure u
u
Maybe u
Nothing -> String -> Get u
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"underflow or overflow"
{-# INLINE getBoundedIntegral #-}
getInt8 :: Bin.Get Int8
getInt8 :: Get Int8
getInt8 = Word8 -> Int8
zagZigInt8 (Word8 -> Int8) -> Get Word8 -> Get Int8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
U.getWord8
{-# INLINE getInt8 #-}
getInt16 :: Bin.Get Int16
getInt16 :: Get Int16
getInt16 = Word16 -> Int16
zagZigInt16 (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
U.getWord16
{-# INLINE getInt16 #-}
getInt32 :: Bin.Get Int32
getInt32 :: Get Int32
getInt32 = Word32 -> Int32
zagZigInt32 (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
U.getWord32
{-# INLINE getInt32 #-}
getInt64 :: Bin.Get Int64
getInt64 :: Get Int64
getInt64 = Word64 -> Int64
zagZigInt64 (Word64 -> Int64) -> Get Word64 -> Get Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
U.getWord64
{-# INLINE getInt64 #-}
getInt :: Bin.Get Int
getInt :: Get Int
getInt = Word -> Int
zagZigInt (Word -> Int) -> Get Word -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word
U.getWord
{-# INLINE getInt #-}
getWord8 :: Bin.Get Word8
getWord8 :: Get Word8
getWord8 = Get Int16 -> Get Word8
forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral Get Int16
getInt16
{-# INLINE getWord8 #-}
getWord16 :: Bin.Get Word16
getWord16 :: Get Word16
getWord16 = Get Int32 -> Get Word16
forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral Get Int32
getInt32
{-# INLINE getWord16 #-}
getWord32 :: Bin.Get Word32
getWord32 :: Get Word32
getWord32 = Get Int64 -> Get Word32
forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral Get Int64
getInt64
{-# INLINE getWord32 #-}
getWord64 :: Bin.Get Word64
getWord64 :: Get Word64
getWord64 = Get Integer -> Get Word64
forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral (Int -> Get Integer
getInteger Int
10)
{-# INLINE getWord64 #-}
getWord :: Bin.Get Word
getWord :: Get Word
getWord = Get Integer -> Get Word
forall s u.
(Bits s, Integral s, Bits u, Integral u) =>
Get s -> Get u
getBoundedIntegral (Int -> Get Integer
getInteger Int
10)
{-# INLINE getWord #-}
{-# INLINE _zigZagInteger #-}
_zigZagInteger :: Integer -> Natural
_zigZagInteger :: Integer -> Natural
_zigZagInteger = \case
IS Int#
x | W# Word#
y <- Int -> Word
zigZagInt (Int# -> Int
I# Int#
x) -> Word# -> Natural
NS Word#
y
IP ByteArray#
x -> ByteArray# -> Natural
NB (ByteArray# -> Word# -> ByteArray#
bigNatShiftL# ByteArray#
x Word#
1##)
IN ByteArray#
x -> ByteArray# -> Natural
NB (ByteArray# -> Word# -> ByteArray#
bigNatShiftL# ByteArray#
x Word#
1## ByteArray# -> Word# -> ByteArray#
`bigNatSubWordUnsafe#` Word#
1##)
{-# INLINE zagZigInteger #-}
zagZigInteger :: Natural -> Integer
zagZigInteger :: Natural -> Integer
zagZigInteger = \case
NS Word#
x | I# Int#
y <- Word -> Int
zagZigInt (Word# -> Word
W# Word#
x) -> Int# -> Integer
IS Int#
y
NB ByteArray#
x
| Word#
0## <- Word# -> Word# -> Word#
and# Word#
1## (ByteArray# -> Int# -> Word#
indexWordArray# ByteArray#
x Int#
0#) -> ByteArray# -> Integer
IP (ByteArray# -> Word# -> ByteArray#
bigNatShiftR# ByteArray#
x Word#
1##)
| Bool
otherwise -> ByteArray# -> Integer
IN (ByteArray# -> Word# -> ByteArray#
bigNatShiftR# (ByteArray# -> Word# -> ByteArray#
bigNatAddWord# ByteArray#
x Word#
1##) Word#
1##)
{-# INLINE unsafeZigZagFixed #-}
unsafeZigZagFixed
:: forall s u. (FiniteBits s, FiniteBits u, Integral s, Integral u) => s -> u
unsafeZigZagFixed :: forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed =
let !n :: Int
n = s -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (s
forall a. HasCallStack => a
undefined :: s) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
in \s
s -> s -> u
forall a b. (Integral a, Num b) => a -> b
fromIntegral (s -> u) -> s -> u
forall a b. (a -> b) -> a -> b
$! s -> s -> s
forall a. Bits a => a -> a -> a
xor (s -> Int -> s
forall a. Bits a => a -> Int -> a
unsafeShiftL s
s Int
1) (s -> Int -> s
forall a. Bits a => a -> Int -> a
unsafeShiftR s
s Int
n)
{-# INLINE unsafeZagZigFixed #-}
unsafeZagZigFixed
:: forall u s. (FiniteBits u, FiniteBits s, Integral u, Integral s) => u -> s
unsafeZagZigFixed :: forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed = \u
u ->
u -> s
forall a b. (Integral a, Num b) => a -> b
fromIntegral (u -> s) -> u -> s
forall a b. (a -> b) -> a -> b
$! u -> u -> u
forall a. Bits a => a -> a -> a
xor (u -> Int -> u
forall a. Bits a => a -> Int -> a
unsafeShiftR u
u Int
1) (u -> u
forall a. Num a => a -> a
negate (u
u u -> u -> u
forall a. Bits a => a -> a -> a
.&. u
1))
{-# INLINE zigZagInt8 #-}
zigZagInt8 :: Int8 -> Word8
zigZagInt8 :: Int8 -> Word8
zigZagInt8 = Int8 -> Word8
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed
{-# INLINE zagZigInt8 #-}
zagZigInt8 :: Word8 -> Int8
zagZigInt8 :: Word8 -> Int8
zagZigInt8 = Word8 -> Int8
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed
{-# INLINE zigZagInt16 #-}
zigZagInt16 :: Int16 -> Word16
zigZagInt16 :: Int16 -> Word16
zigZagInt16 = Int16 -> Word16
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed
{-# INLINE zagZigInt16 #-}
zagZigInt16 :: Word16 -> Int16
zagZigInt16 :: Word16 -> Int16
zagZigInt16 = Word16 -> Int16
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed
{-# INLINE zigZagInt32 #-}
zigZagInt32 :: Int32 -> Word32
zigZagInt32 :: Int32 -> Word32
zigZagInt32 = Int32 -> Word32
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed
{-# INLINE zagZigInt32 #-}
zagZigInt32 :: Word32 -> Int32
zagZigInt32 :: Word32 -> Int32
zagZigInt32 = Word32 -> Int32
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed
{-# INLINE zigZagInt64 #-}
zigZagInt64 :: Int64 -> Word64
zigZagInt64 :: Int64 -> Word64
zigZagInt64 = Int64 -> Word64
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed
{-# INLINE zagZigInt64 #-}
zagZigInt64 :: Word64 -> Int64
zagZigInt64 :: Word64 -> Int64
zagZigInt64 = Word64 -> Int64
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed
{-# INLINE zigZagInt #-}
zigZagInt :: Int -> Word
zigZagInt :: Int -> Word
zigZagInt = Int -> Word
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZigZagFixed
{-# INLINE zagZigInt #-}
zagZigInt :: Word -> Int
zagZigInt :: Word -> Int
zagZigInt = Word -> Int
forall s u.
(FiniteBits s, FiniteBits u, Integral s, Integral u) =>
s -> u
unsafeZagZigFixed
{-# INLINE naturalFromInteger #-}
naturalFromInteger :: MonadFail m => Integer -> m Natural
naturalFromInteger :: forall (m :: * -> *). MonadFail m => Integer -> m Natural
naturalFromInteger = \case
IS Int#
x | Int# -> Bool
isTrue# (Int#
0# Int# -> Int# -> Int#
<=# Int#
x) -> Natural -> m Natural
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Natural -> m Natural) -> Natural -> m Natural
forall a b. (a -> b) -> a -> b
$ Word# -> Natural
naturalFromWord# (Int# -> Word#
int2Word# Int#
x)
IP ByteArray#
x -> Natural -> m Natural
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Natural -> m Natural) -> Natural -> m Natural
forall a b. (a -> b) -> a -> b
$ ByteArray# -> Natural
naturalFromBigNat# ByteArray#
x
Integer
_ -> String -> m Natural
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"underflow"