Skip to content

Commit

Permalink
Export the base64 shimmer
Browse files Browse the repository at this point in the history
  • Loading branch information
imalsogreg committed Aug 3, 2023
1 parent f94b9a6 commit 6a641e5
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 19 deletions.
3 changes: 0 additions & 3 deletions src-ghc/Pact/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,11 +164,8 @@ evalContinuation runner ee cm = case (_cmProof cm) of
Nothing ->
interpret runner (setStep Nothing) (Left Nothing)
Just p -> do
putStrLn "TESTING1"
etpe <- (_spvVerifyContinuation . _eeSPVSupport $ ee) p
putStrLn "TESTING2"
pe <- either contError return etpe
putStrLn "TESTING3"
interpret runner (setStep (_peYield pe)) (Left $ Just pe)
where
contError spvErr =
Expand Down
14 changes: 2 additions & 12 deletions src/Pact/Native.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ import Data.Functor(($>))
import Data.Foldable
import qualified Data.HashMap.Strict as HM
import qualified Data.Map.Strict as M
import qualified Data.List as L (nubBy, stripPrefix)
import qualified Data.List as L (nubBy)
import qualified Data.Set as S
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
Expand Down Expand Up @@ -1371,20 +1371,10 @@ base64decode = defRNative "base64-decode" go
if simplifiedErrorMessage
then "Could not decode string"
else "Could not decode string: "
<> pretty (shimErr e)
<> pretty (base64DowngradeErrorMessage e)
Right t -> return $ tStr t
_ -> argsError i as

-- Convert the errors emitted from base64-bytestring-1.2 into the form
-- used in base64-bytestring-0.1. This is for compatibility with error
-- message produced on-chain prior to pact-4.8.
shimErr :: String -> String
shimErr (L.stripPrefix "invalid character at offset: " -> Just suffix) =
"invalid base64 encoding near offset " <> suffix
shimErr (L.stripPrefix "invalid padding at offset: " -> Just suffix) =
"invalid padding near offset " <> suffix
shimErr errMsg = errMsg

-- | Continue a nested defpact.
-- We get the PactId of the nested defpact from the resolved TDef as a qualified name concatenated with
-- the pactId of the parent.
Expand Down
13 changes: 9 additions & 4 deletions src/Pact/Types/SPV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,16 +27,17 @@ import Control.Lens

import Data.Aeson hiding (Object)
import Data.ByteString
import Data.Default (def)
import Data.Text
import Data.Text.Encoding

import GHC.Generics hiding (to)

import Test.QuickCheck

import Pact.Types.Continuation (PactExec)
import Pact.Types.Continuation (PactExec(PactExec), PactContinuation(PactContinuation))
import Pact.Types.Pretty (Pretty(..), prettyString)
import Pact.Types.Term (Object, Name)
import Pact.Types.Term (Object, Name(Name), PactId(PactId), BareName(BareName))

import qualified Pact.JSON.Encode as J

Expand Down Expand Up @@ -75,5 +76,9 @@ makeLenses ''SPVSupport
noSPVSupport :: SPVSupport
noSPVSupport = SPVSupport spv vcon
where
spv = \_ _ -> return $ Left "SPV verification not supported"
vcon = \_ -> return $ Left "Cross-chain continuations not supported"
spv = \_ obj -> return $ Right obj
vcon = \_ -> return $ Right $ PactExec 2 Nothing Nothing 0
(PactId "somePactId")
(PactContinuation (Name $ BareName "some-defpact-func" def) [])
False
mempty
17 changes: 17 additions & 0 deletions src/Pact/Types/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- Module : Pact.Types.Util
Expand Down Expand Up @@ -34,6 +35,7 @@ module Pact.Types.Util
, encodeBase64UrlUnpadded, decodeBase64UrlUnpadded
, parseB64UrlUnpaddedText, parseB64UrlUnpaddedText'
, toB64UrlUnpaddedText, fromB64UrlUnpaddedText
, base64DowngradeErrorMessage
, B64JsonBytes(..)
-- | AsString
, AsString(..), asString'
Expand Down Expand Up @@ -61,6 +63,7 @@ import qualified Data.ByteString.Lazy.Char8 as BSL8
import qualified Data.ByteString.Short as SB
import qualified Text.Trifecta as Trifecta
import Data.Char
import qualified Data.List as L
import Data.Either (isRight)
import Data.Hashable (Hashable)
import Data.Word
Expand Down Expand Up @@ -332,3 +335,17 @@ arbitraryIdent = cons
letters = "abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZñûüùúūÛÜÙÚŪß"
digits = "0123456789"


-- | Converts the error message format of base64-bytestring-1.2
-- into that of base64-bytestring-0.1, for the error messages
-- that have made it onto the chain.
-- This allows us to upgrade to base64-bytestring-1.2 without
-- breaking compatibility.
base64DowngradeErrorMessage :: String -> String
base64DowngradeErrorMessage
(L.stripPrefix "invalid character at offset: " -> Just suffix) =
"invalid base64 encoding near offset " <> suffix
base64DowngradeErrorMessage
(L.stripPrefix "invalid padding at offset: " -> Just suffix) =
"invalid padding near offset " <> suffix
base64DowngradeErrorMessage errMsg = errMsg

0 comments on commit 6a641e5

Please sign in to comment.