-- SPDX-FileCopyrightText: 2020 Tocqueville Group
--
-- SPDX-License-Identifier: LicenseRef-MIT-TQ

-- | General utilities used by interpreter.
--
-- This is not supposed to import any Michelson modules.
module Morley.Michelson.Interpret.Utils
  ( encodeZarithNumber
  ) where

import Control.Exception (assert)
import qualified Data.Bits as Bits
import qualified Unsafe (fromIntegral)

-- | Encode a number as tezos does this.
--
-- In the Tezos reference implementation this encoding is called @zarith@.
encodeZarithNumber :: Integer -> NonEmpty Word8
encodeZarithNumber :: Integer -> NonEmpty Word8
encodeZarithNumber = Bool -> Integer -> NonEmpty Word8
doEncode Bool
True
  where
    {- Numbers, when packed by tezos, are represented as follows:

    byte 0:         1              _         ______   ||  lowest digits
            has continuation  is negative   payload   ||
                                                      ||
    byte 1:         1                       _______   ||
    ...             1                       _______   ||
    byte n:         0                       _______   ||
            has continuation                payload   \/  highest digits
    -}
    doEncode :: Bool -> Integer -> NonEmpty Word8
    doEncode :: Bool -> Integer -> NonEmpty Word8
doEncode Bool
isFirst Integer
a
      | Integer
a Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
byteWeight =
          let (Integer
hi, 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. (HasCallStack, Integral a, Integral b) => a -> b
Unsafe.fromIntegral @Integer @Word8 Integer
lo) Int
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
>= Integer
0 =
          OneItem (NonEmpty Word8) -> NonEmpty Word8
forall x. One x => OneItem x -> x
one (Integer -> Word8
forall a b. (HasCallStack, Integral a, Integral b) => a -> b
Unsafe.fromIntegral @Integer @Word8 Integer
a)
      | Bool
otherwise = Bool -> NonEmpty Word8 -> NonEmpty Word8
forall a. HasCallStack => Bool -> a -> a
assert Bool
isFirst (NonEmpty Word8 -> NonEmpty Word8)
-> NonEmpty Word8 -> NonEmpty Word8
forall a b. (a -> b) -> a -> b
$
          let Word8
h :| [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 Int
6 Word8 -> [Word8] -> NonEmpty Word8
forall a. a -> [a] -> NonEmpty a
:| [Word8]
t
      where
        byteWeight :: Integer
byteWeight = if Bool
isFirst then Integer
64 else Integer
128