Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
imalsogreg committed Nov 16, 2023
1 parent 172ae6e commit b8471b0
Show file tree
Hide file tree
Showing 7 changed files with 53 additions and 36 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,8 @@ package yet-another-logger
source-repository-package
type: git
location: https://github.com/kadena-io/pact.git
tag: e193c1390c2504862e4eb323e789494fd11cc61d
--sha256: sha256-Llo5dYDcbvtUEHffIhlOvaVmfLNohu7pN3sKJR1c33c=
tag: f978fa4112ec9552f8454807afd3ed2aaf2de777
--sha256: sha256-tUcoYqNq0Vyt3wXxcemd9sHbdsjoqTSbPRQ15wlH0s0=

source-repository-package
type: git
Expand Down
2 changes: 1 addition & 1 deletion src/Chainweb/Pact/PactService/ExecBlock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -257,7 +257,7 @@ validateChainwebTxs logger v cid cp txValidationTime bh txs doBuyGas
sigs = P._cmdSigs t
signers = P._pSigners $ payloadObj $ P._cmdPayload t
validSchemes = validPPKSchemes v cid bh
validProv = validWebAuthnSignatureProvenance v cid bh
validProv = validWebAuthnSignatureEncoding v cid bh

initTxList :: ValidateTxs
initTxList = V.map Right txs
Expand Down
4 changes: 2 additions & 2 deletions src/Chainweb/Pact/RestAPI/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ import qualified Chainweb.TreeDB as TreeDB
import Chainweb.Utils
import Chainweb.Version
import Chainweb.Pact.Validations (assertCommand)
import Chainweb.Version.Guards (validPPKSchemes, validWebAuthnSignatureProvenance)
import Chainweb.Version.Guards (validPPKSchemes, validWebAuthnSignatureEncoding)
import Chainweb.WebPactExecutionService

import Chainweb.Storage.Table
Expand Down Expand Up @@ -696,7 +696,7 @@ validateCommand v cid cmdText = case parsedPayload of
if assertCommand
commandParsed
(validPPKSchemes v cid maxBound)
(validWebAuthnSignatureProvenance v cid maxBound)
(validWebAuthnSignatureEncoding v cid maxBound)
then Right commandParsed
else Left "Command failed validation"
Left e -> Left $ "Pact parsing error: " ++ e
Expand Down
16 changes: 8 additions & 8 deletions src/Chainweb/Pact/Validations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ import Chainweb.Pact.Service.Types
import Chainweb.Time (Seconds(..), Time(..), secondsToTimeSpan, scaleTimeSpan, second, add)
import Chainweb.Transaction (cmdTimeToLive, cmdCreationTime, PayloadWithText, payloadBytes, payloadObj)
import Chainweb.Version
import Chainweb.Version.Guards (validPPKSchemes, validWebAuthnSignatureProvenance)
import Chainweb.Version.Guards (validPPKSchemes, validWebAuthnSignatureEncoding)

import qualified Pact.Types.Gas as P
import qualified Pact.Types.Hash as P
Expand All @@ -78,7 +78,7 @@ assertLocalMetadata cmd@(P.Command pay sigs hsh) txCtx sigVerify = do

let bh = ctxCurrentBlockHeight txCtx
let validSchemes = validPPKSchemes v cid bh
let validProv = validWebAuthnSignatureProvenance v cid bh
let validProv = validWebAuthnSignatureEncoding v cid bh

let P.PublicMeta pcid _ gl gp _ _ = P._pMeta pay
nid = P._pNetworkId pay
Expand Down Expand Up @@ -160,8 +160,8 @@ assertTxSize initialGas gasLimit = initialGas < fromIntegral gasLimit
-- | Check and assert that signers and user signatures are valid for a given
-- transaction hash.
--
assertValidateSigs :: [P.PPKScheme] -> [P.WebAuthnSigProvenance] -> P.PactHash -> [P.Signer] -> [P.UserSig] -> Bool
assertValidateSigs validSchemes validProvenance hsh signers sigs
assertValidateSigs :: [P.PPKScheme] -> [P.WebAuthnSigEncoding] -> P.PactHash -> [P.Signer] -> [P.UserSig] -> Bool
assertValidateSigs validSchemes validEncoding hsh signers sigs
| length signers /= length sigs = False
| otherwise = and $ zipWith verifyUserSig sigs signers
where verifyUserSig sig signer =
Expand All @@ -170,7 +170,7 @@ assertValidateSigs validSchemes validProvenance hsh signers sigs
okScheme = sigScheme `elem` validSchemes
okSignature = isRight $ P.verifyUserSig hsh sig signer
okProvenance = case sig of
P.WebAuthnSig _ provenance -> provenance `elem` validProvenance
P.WebAuthnSig _ provenance -> provenance `elem` validEncoding
_ -> True
in okScheme && okProvenance && okSignature

Expand Down Expand Up @@ -200,10 +200,10 @@ assertTxTimeRelativeToParent (ParentCreationTime (BlockCreationTime txValidation

-- | Assert that the command hash matches its payload and
-- its signatures are valid, without parsing the payload.
assertCommand :: P.Command PayloadWithText -> [P.PPKScheme] -> [P.WebAuthnSigProvenance] -> Bool
assertCommand (P.Command pwt sigs hsh) ppkSchemePassList validWebAuthnProvenance =
assertCommand :: P.Command PayloadWithText -> [P.PPKScheme] -> [P.WebAuthnSigEncoding] -> Bool
assertCommand (P.Command pwt sigs hsh) ppkSchemePassList validWebAuthnEncoding =
isRight assertHash &&
assertValidateSigs ppkSchemePassList validWebAuthnProvenance hsh signers sigs
assertValidateSigs ppkSchemePassList validWebAuthnEncoding hsh signers sigs
where
cmdBS = SBS.fromShort $ payloadBytes pwt
signers = P._pSigners (payloadObj pwt)
Expand Down
10 changes: 5 additions & 5 deletions src/Chainweb/Version/Guards.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ module Chainweb.Version.Guards
, maxBlockGasLimit
, validPPKSchemes
, validKeyFormats
, validWebAuthnSignatureProvenance
, validWebAuthnSignatureEncoding

-- ** BlockHeader Validation Guards
, slowEpochGuard
Expand All @@ -62,7 +62,7 @@ import Control.Lens
import Numeric.Natural
import Pact.Types.KeySet (PublicKeyText, ed25519HexFormat, webAuthnFormat)
import Pact.Types.Scheme (PPKScheme(ED25519, WebAuthn))
import Pact.Types.Crypto (WebAuthnSigProvenance(WebAuthnStringified, WebAuthnObject))
import Pact.Types.Crypto (WebAuthnSigEncoding(WebAuthnStringified, WebAuthnObject))

import Chainweb.BlockHeight
import Chainweb.ChainId
Expand Down Expand Up @@ -272,10 +272,10 @@ validKeyFormats v cid bh =
then [ed25519HexFormat, webAuthnFormat]
else [ed25519HexFormat]

-- | Different versions of Chainweb allow different WebAuthn signature provenance.
-- | Different versions of Chainweb allow different WebAuthn signature encoding.
--
validWebAuthnSignatureProvenance :: ChainwebVersion -> ChainId -> BlockHeight -> [WebAuthnSigProvenance]
validWebAuthnSignatureProvenance v cid bh =
validWebAuthnSignatureEncoding :: ChainwebVersion -> ChainId -> BlockHeight -> [WebAuthnSigEncoding]
validWebAuthnSignatureEncoding v cid bh =
if chainweb222Pact v cid bh
then [WebAuthnStringified, WebAuthnObject]
else [WebAuthnStringified]
24 changes: 15 additions & 9 deletions test/Chainweb/Test/Pact/PactMultiChainTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ import Test.Tasty.HUnit
import Pact.Types.Capability
import Pact.Types.Command
import Pact.Types.Continuation
import Pact.Types.Crypto (WebAuthnSigEncoding(WebAuthnObject, WebAuthnStringified))
import Pact.Types.Hash
import Pact.Types.PactError
import Pact.Types.PactValue
Expand Down Expand Up @@ -1095,10 +1096,14 @@ pact49UpgradeTest = do

pact410UpgradeTest :: PactTestM ()
pact410UpgradeTest = do
runToHeight 114
runToHeight 80

runBlockTest
[ PactTxTest (buildBasicGasWebAuthn 1000 $ mkExec' "(+ 1 2)") $ assertTxSuccess "Should succeed" (pInteger 3) ]
[ PactTxTest (buildBasicGasWebAuthn WebAuthnObject 1000 $ mkExec' "(+ 1 2)") $
assertTxSuccess "Should succeed" (pInteger 3)
, PactTxTest (buildBasicGasWebAuthn WebAuthnStringified 1000 $ mkExec' "(+ 1 3)") $
assertTxSuccess "Should succeed" (pInteger 4)
]


pact4coin3UpgradeTest :: PactTestM ()
Expand Down Expand Up @@ -1399,8 +1404,8 @@ buildXReceive
buildXReceive (proof,pid) = buildBasic $
mkCont ((mkContMsg pid 1) { _cmProof = Just proof })

signWebAuthn00 :: CmdBuilder -> CmdBuilder
signWebAuthn00 = set cbSigners [mkWebAuthnSigner' sender02WebAuthn []]
signWebAuthn00 :: WebAuthnSigEncoding -> CmdBuilder -> CmdBuilder
signWebAuthn00 webAuthnSigEncoding = set cbSigners [mkWebAuthnSigner' sender02WebAuthn [] webAuthnSigEncoding]

signSender00 :: CmdBuilder -> CmdBuilder
signSender00 = set cbSigners [mkEd25519Signer' sender00 []]
Expand Down Expand Up @@ -1430,17 +1435,18 @@ buildBasic' f r = MempoolCmdBuilder $ \(MempoolInput _ bh) ->
$ mkCmd (sshow bh) r

buildBasicWebAuthn'
:: (CmdBuilder -> CmdBuilder)
:: WebAuthnSigEncoding
-> (CmdBuilder -> CmdBuilder)
-> PactRPC T.Text
-> MempoolCmdBuilder
buildBasicWebAuthn' f r = MempoolCmdBuilder $ \(MempoolInput _ bh) ->
f $ signWebAuthn00
buildBasicWebAuthn' webAuthnSigEncoding f r = MempoolCmdBuilder $ \(MempoolInput _ bh) ->
f $ signWebAuthn00 webAuthnSigEncoding
$ setFromHeader bh
$ mkCmd (sshow bh) r


buildBasicGasWebAuthn :: GasLimit -> PactRPC T.Text -> MempoolCmdBuilder
buildBasicGasWebAuthn g = buildBasicWebAuthn' (set cbGasLimit g)
buildBasicGasWebAuthn :: WebAuthnSigEncoding -> GasLimit -> PactRPC T.Text -> MempoolCmdBuilder
buildBasicGasWebAuthn webAuthnSigEncoding g = buildBasicWebAuthn' webAuthnSigEncoding (set cbGasLimit g)


-- | Get output on latest cut for chain
Expand Down
29 changes: 20 additions & 9 deletions test/Chainweb/Test/Pact/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ module Chainweb.Test.Pact.Utils
, sender01
, sender00Ks
, sender02WebAuthn
, sender03WebAuthn
, allocation00KeyPair
, testKeyPairs
, mkKeySetData
Expand Down Expand Up @@ -81,6 +82,7 @@ module Chainweb.Test.Pact.Utils
, CmdSigner
, csSigner
, csPrivKey
, csWebAuthnEncoding
-- * Pact Service creation
, withPactTestBlockDb
, withWebPactExecutionService
Expand Down Expand Up @@ -232,6 +234,11 @@ sender02WebAuthn =
("a4010103272006215820c18831c6f15306d6271e154842906b68f26c1af79b132dde6f6add79710303bf"
,"fecd4feb1243d715d095e24713875ca76c476f8672ec487be8e3bc110dd329ab")

sender03WebAuthn :: SimpleKeyPair
sender03WebAuthn =
("a4010103272006215820ad72392508272b4c45536976474cdd434e772bfd630738ee9aac7343e7222eb6"
,"ebe7d1119a53863fa64be7347d82d9fcc9ebeb8cbbe480f5e8642c5c36831434")

allocation00KeyPair :: SimpleKeyPair
allocation00KeyPair =
( "d82d0dcde9825505d86afb6dcc10411d6b67a429a79e21bda4bb119bf28ab871"
Expand Down Expand Up @@ -455,8 +462,8 @@ mkGasCap = mkCoinCap "GAS" []
data CmdSigner = CmdSigner
{ _csSigner :: !Signer
, _csPrivKey :: !Text
, _csWebAuthnEncoding :: Maybe WebAuthnProvenance
-- ^ When this field is set, we override the WebAuthn provenance
, _csWebAuthnEncoding :: WebAuthnSigEncoding
-- ^ When this field is set, we override the WebAuthn encoding
-- of the signatures in order to influence how the signatures
-- will be encoded. This is used for testing.
} deriving (Eq,Show,Ord,Generic)
Expand All @@ -465,7 +472,9 @@ data CmdSigner = CmdSigner
mkEd25519Signer :: Text -> Text -> [SigCapability] -> CmdSigner
mkEd25519Signer pubKey privKey caps = CmdSigner
{ _csSigner = signer
, _csPrivKey = privKey }
, _csPrivKey = privKey
, _csWebAuthnEncoding = WebAuthnObject
}
where
signer = Signer
{ _siScheme = Nothing
Expand All @@ -476,19 +485,21 @@ mkEd25519Signer pubKey privKey caps = CmdSigner
mkEd25519Signer' :: SimpleKeyPair -> [SigCapability] -> CmdSigner
mkEd25519Signer' (pub,priv) = mkEd25519Signer pub priv

mkWebAuthnSigner :: Text -> Text -> [SigCapability] -> CmdSigner
mkWebAuthnSigner pubKey privKey caps = CmdSigner
mkWebAuthnSigner :: Text -> Text -> [SigCapability] -> WebAuthnSigEncoding -> CmdSigner
mkWebAuthnSigner pubKey privKey caps prov = CmdSigner
{ _csSigner = signer
, _csPrivKey = privKey }
, _csPrivKey = privKey
, _csWebAuthnEncoding = prov
}
where
signer = Signer
{ _siScheme = Just WebAuthn
, _siPubKey = pubKey
, _siAddress = Nothing
, _siCapList = caps }

mkWebAuthnSigner' :: SimpleKeyPair -> [SigCapability] -> CmdSigner
mkWebAuthnSigner' (pub, priv) = mkWebAuthnSigner pub priv
mkWebAuthnSigner' :: SimpleKeyPair -> [SigCapability] -> WebAuthnSigEncoding -> CmdSigner
mkWebAuthnSigner' (pub, priv) caps prov = mkWebAuthnSigner pub priv caps prov

-- | Chainweb-oriented command builder.
data CmdBuilder = CmdBuilder
Expand Down Expand Up @@ -578,7 +589,7 @@ dieL :: MonadThrow m => [Char] -> Either [Char] a -> m a
dieL msg = either (\s -> throwM $ userError $ msg ++ ": " ++ s) return

toApiKp :: MonadThrow m => CmdSigner -> m ApiKeyPair
toApiKp (CmdSigner Signer{..} privKey) = do
toApiKp (CmdSigner Signer{..} privKey _webAuthnEncoding) = do
sk <- dieL "private key" $ parseB16TextOnly privKey
pk <- dieL "public key" $ parseB16TextOnly _siPubKey
return $!
Expand Down

0 comments on commit b8471b0

Please sign in to comment.