module Michelson.Interpret.Utils
( encodeZarithNumber
) where
import Control.Exception (assert)
import qualified Data.Bits as Bits
encodeZarithNumber :: Integer -> NonEmpty Word8
encodeZarithNumber :: Integer -> NonEmpty Word8
encodeZarithNumber = Bool -> Integer -> NonEmpty Word8
doEncode Bool
True
where
doEncode :: Bool -> Integer -> NonEmpty Word8
doEncode :: Bool -> Integer -> NonEmpty Word8
doEncode isFirst :: Bool
isFirst a :: Integer
a
| Integer
a Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
byteWeight =
let (hi :: Integer
hi, lo :: Integer
lo) = Integer
a Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`divMod` Integer
byteWeight
byte :: Word8
byte = Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
Bits.setBit (Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral @_ @Word8 Integer
lo) 7
in Word8
byte Word8 -> [Word8] -> NonEmpty Word8
forall a. a -> [a] -> NonEmpty a
:| NonEmpty Word8 -> [Element (NonEmpty Word8)]
forall t. Container t => t -> [Element t]
toList (Bool -> Integer -> NonEmpty Word8
doEncode Bool
False Integer
hi)
| Integer
a Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 =
OneItem (NonEmpty Word8) -> NonEmpty Word8
forall x. One x => OneItem x -> x
one (Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral @_ @Word8 Integer
a)
| Bool
otherwise = Bool -> NonEmpty Word8 -> NonEmpty Word8
forall a. (?callStack::CallStack) => Bool -> a -> a
assert Bool
isFirst (NonEmpty Word8 -> NonEmpty Word8)
-> NonEmpty Word8 -> NonEmpty Word8
forall a b. (a -> b) -> a -> b
$
let h :: Word8
h :| t :: [Word8]
t = Bool -> Integer -> NonEmpty Word8
doEncode Bool
True (-Integer
a)
in Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
Bits.setBit Word8
h 6 Word8 -> [Word8] -> NonEmpty Word8
forall a. a -> [a] -> NonEmpty a
:| [Word8]
t
where
byteWeight :: Integer
byteWeight = if Bool
isFirst then 64 else 128