Skip to content

Commit

Permalink
Merge pull request #188 from kadena-io/push-pxkqyytxyusu
Browse files Browse the repository at this point in the history
Use PactValue for data field
  • Loading branch information
edmundnoble authored Jul 23, 2024
2 parents 98558ed + 5a113fe commit 875a787
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 36 deletions.
36 changes: 18 additions & 18 deletions pact-request-api/Pact/Core/Command/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,6 @@ import Data.List.NonEmpty (NonEmpty(..))

import Pact.Time
import Pact.JSON.Yaml
import Pact.JSON.Legacy.Value
import System.FilePath
import qualified Pact.JSON.Encode as J
import qualified Pact.JSON.Decode as JD
Expand Down Expand Up @@ -206,7 +205,7 @@ data ApiReq = ApiReq {
_ylPactTxHash :: Maybe Hash,
_ylStep :: Maybe Int,
_ylRollback :: Maybe Bool,
_ylData :: Maybe JD.Value,
_ylData :: Maybe PactValue,
_ylProof :: Maybe ContProof,
_ylDataFile :: Maybe FilePath,
_ylCode :: Maybe Text,
Expand All @@ -223,7 +222,7 @@ instance JD.FromJSON ApiReq where
parseJSON = JD.withObject "ApiReq" $ \o -> do
publicMeta <- o JD..:? "publicMeta"
proof <- o JD..:? "proof"
data_ <- o JD..:? "data"
data_ <- (fmap . fmap) _stableEncoding (o JD..:? "data")
networkId <- o JD..:? "networkId"
rollback <- o JD..:? "rollback"
signers <- o JD..:? "signers"
Expand Down Expand Up @@ -258,7 +257,7 @@ instance J.Encode ApiReq where
build o = J.object
[ "publicMeta" J..= _ylPublicMeta o
, "proof" J..= _ylProof o
, "data" J..= _ylData o
, "data" J..= StableEncoding (_ylData o)
, "networkId" J..= _ylNetworkId o
, "rollback" J..= _ylRollback o
, "signers" J..= fmap J.Array (_ylSigners o)
Expand Down Expand Up @@ -420,7 +419,8 @@ returnSigDataOrCommand outputLocal sd
returnCommandIfDone :: Bool -> SigData Text -> IO ByteString
returnCommandIfDone outputLocal sd =
case sigDataToCommand sd of
Left _ -> return $ encodeYamlWith yamlOptions sd
Left _ -> do
return $ encodeYamlWith yamlOptions sd
Right c -> do
let res = verifyCommand $ fmap T.encodeUtf8 c
out = if outputLocal then J.encode c else J.encode (SubmitBatch (c :| []))
Expand Down Expand Up @@ -480,7 +480,7 @@ uapiReq' fp p = do

-- | parts read/rationalized from a processed ApiReq:
-- the ApiReq, code, msg data, PublicMeta
type ApiReqParts = (ApiReq,Text,A.Value,PublicMeta)
type ApiReqParts = (ApiReq,Text,PactValue,PublicMeta)

-- | Assemble a command and parts from a ApiReq YAML file.
mkApiReq :: FilePath -> IO (ApiReqParts,Command Text)
Expand Down Expand Up @@ -559,9 +559,9 @@ mkApiReqExec unsignedReq ar@ApiReq{..} fp = do
cdata <- case (_ylDataFile,_ylData) of
(Nothing,Just v) -> return v -- either (\e -> dieAR $ "Data decode failed: " ++ show e) return $ eitherDecode (BSL.pack v)
(Just f,Nothing) -> (BSL.readFile (dir </> f)) >>=
either (\e -> dieAR $ "Data file load failed: " ++ show e) return .
either (\e -> dieAR $ "Data file load failed: " ++ show e) (return . _stableEncoding) .
JD.eitherDecode
(Nothing,Nothing) -> return A.Null
(Nothing,Nothing) -> return PUnit
_ -> dieAR "Expected either a 'data' or 'dataFile' entry, or neither"
return (code,cdata)
pubMeta <- mkPubMeta _ylPublicMeta
Expand Down Expand Up @@ -606,7 +606,7 @@ mkNonce = maybe (T.pack . show <$> getCurrentTime) return
mkExec
:: Text
-- ^ code
-> A.Value
-> PactValue
-- ^ optional environment data
-> PublicMeta
-- ^ public metadata
Expand All @@ -627,15 +627,15 @@ mkExec code mdata pubMeta kps ves nid ridm = do
(StableEncoding pubMeta)
rid
nid
(Exec (ExecMsg code (toLegacyJson mdata)))
(Exec (ExecMsg code mdata))
return $ T.decodeUtf8 <$> cmd

-- | Construct an Exec request message
--
mkUnsignedExec
:: Text
-- ^ code
-> A.Value
-> PactValue
-- ^ optional environment data
-> PublicMeta
-- ^ public metadata
Expand All @@ -656,7 +656,7 @@ mkUnsignedExec code mdata pubMeta kps ves nid ridm = do
(StableEncoding pubMeta)
rid
nid
(Exec (ExecMsg code (toLegacyJson mdata)))
(Exec (ExecMsg code mdata))
return $ T.decodeUtf8 <$> cmd


Expand All @@ -679,9 +679,9 @@ mkApiReqCont unsignedReq ar@ApiReq{..} fp = do
case (_ylDataFile,_ylData) of
(Nothing,Just v) -> return v -- either (\e -> dieAR $ "Data decode failed: " ++ show e) return $ eitherDecode (BSL.pack v)
(Just f,Nothing) -> BSL.readFile (dir </> f) >>=
either (\e -> dieAR $ "Data file load failed: " ++ show e) return .
either (\e -> dieAR $ "Data file load failed: " ++ show e) (return . _stableEncoding) .
JD.eitherDecode
(Nothing,Nothing) -> return A.Null
(Nothing,Nothing) -> return PUnit
_ -> dieAR "Expected either a 'data' or 'dataFile' entry, or neither"
let pactId = (DefPactId . hashToText) apiPactId
pubMeta <- mkPubMeta _ylPublicMeta
Expand All @@ -699,7 +699,7 @@ mkCont
-- ^ cont step
-> Bool
-- ^ has rollback?
-> A.Value
-> PactValue
-- ^ environment data
-> PublicMeta
-- ^ command public metadata
Expand All @@ -722,7 +722,7 @@ mkCont txid step rollback mdata pubMeta kps ves ridm proof nid = do
(StableEncoding pubMeta)
rid
nid
(Continuation (ContMsg txid step rollback (toLegacyJson mdata) proof) :: (PactRPC ContMsg))
(Continuation (ContMsg txid step rollback mdata proof) :: (PactRPC ContMsg))
return $ T.decodeUtf8 <$> cmd


Expand All @@ -735,7 +735,7 @@ mkUnsignedCont
-- ^ cont step
-> Bool
-- ^ has rollback?
-> A.Value
-> PactValue
-- ^ environment data
-> PublicMeta
-- ^ command public metadata
Expand All @@ -758,7 +758,7 @@ mkUnsignedCont txid step rollback mdata pubMeta kps ves ridm proof nid = do
(StableEncoding pubMeta)
(T.pack $ show rid)
nid
(Continuation (ContMsg txid step rollback (toLegacyJson mdata) proof) :: (PactRPC ContMsg))
(Continuation (ContMsg txid step rollback mdata proof) :: (PactRPC ContMsg))
return $ T.decodeUtf8 <$> cmd

-- | Construct a `Command` from a `PactRPC` request, a nonce, and a set of credentials.
Expand Down
15 changes: 7 additions & 8 deletions pact-request-api/Pact/Core/Command/RPC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,14 +27,13 @@ import Control.DeepSeq

import GHC.Generics

import Pact.JSON.Legacy.Value

import Pact.Core.SPV
import Pact.Core.Names

import Pact.JSON.Decode
import Pact.Core.StableEncoding
import qualified Pact.JSON.Encode as J
import Pact.Core.PactValue


data PactRPC c =
Expand All @@ -56,20 +55,20 @@ instance J.Encode c => J.Encode (PactRPC c) where

data ExecMsg c = ExecMsg
{ _pmCode :: c
, _pmData :: LegacyValue
, _pmData :: PactValue
} deriving (Eq,Generic,Show,Functor,Foldable,Traversable)

instance NFData c => NFData (ExecMsg c)
instance FromJSON c => FromJSON (ExecMsg c) where
parseJSON =
withObject "PactMsg" $ \o ->
ExecMsg <$> o .: "code" <*> o .: "data"
ExecMsg <$> o .: "code" <*> (maybe PUnit _stableEncoding <$> o .:? "data")
{-# INLINE parseJSON #-}


instance J.Encode c => J.Encode (ExecMsg c) where
build o = J.object
[ "data" J..= _pmData o
[ "data" J..= StableEncoding (_pmData o)
, "code" J..= _pmCode o
]
{-# INLINE build #-}
Expand All @@ -78,7 +77,7 @@ data ContMsg = ContMsg
{ _cmPactId :: !DefPactId
, _cmStep :: !Int
, _cmRollback :: !Bool
, _cmData :: !LegacyValue
, _cmData :: !PactValue
, _cmProof :: !(Maybe ContProof)
} deriving (Eq,Show,Generic)

Expand All @@ -89,7 +88,7 @@ instance FromJSON ContMsg where
StableEncoding defPactId <- o .: "pactId"
step <- o .: "step"
rollback <- o .: "rollback"
msgData <- o .: "data"
StableEncoding msgData <- o .: "data"
maybeProof <- o .:? "proof"
pure $ ContMsg defPactId step rollback msgData maybeProof
-- ContMsg <$> o .: "pactId" <*> o .: "step" <*> o .: "rollback" <*> o .: "data"
Expand All @@ -99,7 +98,7 @@ instance FromJSON ContMsg where
instance J.Encode ContMsg where
build o = J.object
[ "proof" J..= _cmProof o
, "data" J..= _cmData o
, "data" J..= StableEncoding (_cmData o)
, "pactId" J..= StableEncoding (_cmPactId o)
, "rollback" J..= _cmRollback o
, "step" J..= J.Aeson (_cmStep o)
Expand Down
6 changes: 3 additions & 3 deletions pact-tests/Pact/Core/Test/CommandTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Data.Text
import Test.Tasty
import Test.Tasty.HUnit

import Pact.JSON.Legacy.Value
import Pact.Core.PactValue

import Pact.Core.Command.Client
import Pact.Core.Command.Crypto (generateEd25519KeyPair)
Expand All @@ -23,7 +23,7 @@ import Pact.Core.Command.Types
exampleCommand :: IO (Command ByteString)
exampleCommand = do
testKeyPair <- generateEd25519KeyPair
let rpc :: PactRPC Text = Exec $ ExecMsg { _pmCode = "(+ 1 2)", _pmData = LegacyValue A.Null}
let rpc :: PactRPC Text = Exec $ ExecMsg { _pmCode = "(+ 1 2)", _pmData = PUnit}
let metaData = A.Number 1 :: A.Value
mkCommand [(testKeyPair, [])] [] metaData "nonce" Nothing rpc

Expand All @@ -37,6 +37,6 @@ tests = do
ProcFail f -> do
print f
assertFailure "Command should be valid"
ProcSucc _ ->
ProcSucc _ ->
assertBool "Command should be valid" True
]
4 changes: 1 addition & 3 deletions pact-tests/Pact/Core/Test/SignatureSchemeTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,15 +13,13 @@ import qualified Data.Text.Encoding as T
import Data.Text.Encoding
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Aeson as A
import qualified Control.Lens as Lens
import qualified Data.ByteString.Base16 as B16

import Pact.Core.Capabilities
import Pact.Core.Command.Types
import Pact.Core.Command.Crypto
import Pact.Core.Command.Client
import Pact.JSON.Legacy.Value
import qualified Pact.JSON.Encode as J
import Pact.Core.Names
import Pact.Core.PactValue
Expand Down Expand Up @@ -87,7 +85,7 @@ toSigners kps = return $ map makeSigner kps
toExecPayload :: [Signer QualifiedName PactValue] -> Text -> ByteString
toExecPayload signers t = J.encodeStrict payload
where
payload = Payload (Exec (ExecMsg t $ toLegacyJson Null)) "nonce" (J.Aeson ()) signers Nothing Nothing
payload = Payload (Exec (ExecMsg t $ PUnit)) "nonce" (J.Aeson ()) signers Nothing Nothing


shouldBeProcFail :: ProcessedCommand () ParsedCode -> Assertion
Expand Down
14 changes: 10 additions & 4 deletions pact/Pact/Core/StableEncoding.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ module Pact.Core.StableEncoding
where

import Control.Applicative
import Control.Monad (guard)
import qualified Data.Aeson.KeyMap as Aeson
import qualified Data.Aeson.Key as AesonKey
import Data.Aeson.Types (Value(Number), Parser)
Expand Down Expand Up @@ -108,7 +109,7 @@ instance J.Encode (StableEncoding Literal) where
encodeDecimal d@(Decimal _ mantissa)
| isSafeInteger mantissa = J.build $ J.Aeson @Scientific $ fromRational $ toRational d
| otherwise = J.object [ "decimal" J..= T.pack (show d) ]
encodeUnit = J.object ["unit" J..= T.empty] -- TODO: Discuss?
encodeUnit = J.object ["##unit" J..= T.empty] -- TODO: Discuss?
isSafeInteger i = i >= -9007199254740991 && i <= 9007199254740991
{-# INLINABLE build #-}

Expand Down Expand Up @@ -443,10 +444,15 @@ instance JD.FromJSON (StableEncoding Literal) where
parseJSON n@JD.Number{} = StableEncoding . LDecimal <$> decoder decimalCodec n
parseJSON (JD.String s) = pure $ StableEncoding $ LString s
parseJSON (JD.Bool b) = pure $ StableEncoding $ LBool b
parseJSON o@JD.Object {} =
parseJSON o@(JD.Object o') =
(StableEncoding . LInteger <$> decoder integerCodec o) <|>
-- (LTime <$> decoder timeCodec o) <|>
(StableEncoding . LDecimal <$> decoder decimalCodec o)
(StableEncoding . LDecimal <$> decoder decimalCodec o) <|>
(StableEncoding <$> decodeUnit)
where
decodeUnit = do
v <- o' JD..: "##unit"
guard (T.null v)
pure LUnit
parseJSON _t = fail "Literal parse failed"

instance J.Encode (StableEncoding name) => J.Encode (StableEncoding (CapToken name PactValue)) where
Expand Down

0 comments on commit 875a787

Please sign in to comment.