From d12eb5359df6fea6da5ea705dec7ec30db13e4dc Mon Sep 17 00:00:00 2001 From: Paul Cadman Date: Fri, 31 May 2024 12:03:36 +0100 Subject: [PATCH] Use little endian encoding of ByteStrings in Anoma Anoma decodes integer atoms as bytes assuming a little endian layout. This commit adds functions byteStringToIntegerLE and integerToByteStringLE that makes it clear that little endian encoding is being used. --- .../Compiler/Nockma/Encoding/ByteString.hs | 34 ++++++++++--------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/src/Juvix/Compiler/Nockma/Encoding/ByteString.hs b/src/Juvix/Compiler/Nockma/Encoding/ByteString.hs index 13ebbf7c1e..446705eefc 100644 --- a/src/Juvix/Compiler/Nockma/Encoding/ByteString.hs +++ b/src/Juvix/Compiler/Nockma/Encoding/ByteString.hs @@ -1,7 +1,8 @@ module Juvix.Compiler.Nockma.Encoding.ByteString where -import Data.Bit -import Juvix.Compiler.Nockma.Encoding.Base +import Data.Bits +import Data.ByteString qualified as BS +import Data.ByteString.Builder qualified as BS import Juvix.Compiler.Nockma.Language import Juvix.Prelude.Base @@ -12,19 +13,24 @@ byteStringToAtom :: (NockNatural a, Member (Error (ErrNockNatural a)) r) => Byte byteStringToAtom = fmap mkEmptyAtom . fromNatural . byteStringToNatural byteStringToNatural :: ByteString -> Natural -byteStringToNatural = bitsToNatural . cloneFromByteString +byteStringToNatural = fromInteger . byteStringToIntegerLE naturalToByteString :: Natural -> ByteString -naturalToByteString = cloneToByteString . naturalToBits +naturalToByteString = integerToByteStringLE . toInteger -textToNatural :: Text -> Natural -textToNatural = byteStringToNatural . encodeUtf8 +byteStringToIntegerLE :: ByteString -> Integer +byteStringToIntegerLE = BS.foldr (\b acc -> acc `shiftL` 8 .|. fromIntegral b) 0 -bitsToNatural :: Vector Bit -> Natural -bitsToNatural = fromInteger . vectorBitsToInteger +integerToByteStringLE :: Integer -> ByteString +integerToByteStringLE = BS.toStrict . BS.toLazyByteString . go + where + go :: Integer -> BS.Builder + go = \case + 0 -> mempty + n -> BS.word8 (fromIntegral n) <> go (n `shiftR` 8) -naturalToBits :: Natural -> Vector Bit -naturalToBits = integerToVectorBits . toInteger +textToNatural :: Text -> Natural +textToNatural = byteStringToNatural . encodeUtf8 atomToText :: (NockNatural a, Member (Error (ErrNockNatural a)) r) => Atom a -> Sem r Text atomToText = fmap decodeUtf8Lenient . atomToByteString @@ -32,13 +38,9 @@ atomToText = fmap decodeUtf8Lenient . atomToByteString -- | Construct an atom formed by concatenating the bits of two atoms, where each atom represents a sequence of bytes atomConcatenateBytes :: forall a r. (NockNatural a, Member (Error (ErrNockNatural a)) r) => Atom a -> Atom a -> Sem r (Atom a) atomConcatenateBytes l r = do - -- cloneToByteString ensures that the bytestring is zero-padded up to the byte boundary - lBs <- cloneToByteString <$> atomToBits l - rBs <- cloneToByteString <$> atomToBits r + lBs <- atomToByteString l + rBs <- atomToByteString r byteStringToAtom (lBs <> rBs) - where - atomToBits :: Atom a -> Sem r (Vector Bit) - atomToBits = fmap naturalToBits . nockNatural mkEmptyAtom :: a -> Atom a mkEmptyAtom x =