Skip to content

Commit

Permalink
Merge remote-tracking branch 'origin/master' into ana/asdata-product-…
Browse files Browse the repository at this point in the history
…types
  • Loading branch information
ana-pantilie committed Feb 18, 2025
2 parents 1ee3678 + 262adfd commit ddfbdef
Show file tree
Hide file tree
Showing 60 changed files with 410 additions and 93 deletions.
4 changes: 2 additions & 2 deletions doc/notes/model/UTxO.hsproj/Examples/Keys.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,10 @@
module Examples.Keys
where

import "cryptonite" Crypto.PubKey.ECC.ECDSA
import "crypton" Crypto.PubKey.ECC.ECDSA
import Crypto.PubKey.ECC.Generate
import Crypto.PubKey.ECC.Types
import "cryptonite" Crypto.Random
import "crypton" Crypto.Random

import Data.Map (Map)
import Data.Map qualified as Map
Expand Down
2 changes: 1 addition & 1 deletion doc/notes/model/UTxO.hsproj/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
module Types
where

import "cryptonite" Crypto.Hash
import "crypton" Crypto.Hash


-- Basic types
Expand Down
5 changes: 3 additions & 2 deletions doc/notes/model/UTxO.hsproj/UTxO.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ x-ghc-framework-version: 8.0.2-9.6-1
x-last-ide-version: HfM1.6.0

executable UTxO
main-is: Main.hs
main-is: Main.hs
build-depends:
base
, bytestring
Expand All @@ -26,7 +26,8 @@ executable UTxO
, memory
, template-haskell

default-language: Haskell2010
default-language: Haskell2010
default-extensions: ImportQualifiedPost
other-modules:
Examples.Keys
Examples.PubKey
Expand Down
4 changes: 2 additions & 2 deletions doc/notes/model/UTxO.hsproj/Witness.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,8 @@ module Witness (
validate
) where

import "cryptonite" Crypto.Hash
import "cryptonite" Crypto.PubKey.ECC.ECDSA
import "crypton" Crypto.Hash
import "crypton" Crypto.PubKey.ECC.ECDSA
import Data.ByteArray qualified as BA
import Data.ByteString.Char8 qualified as BS
import Language.Haskell.TH
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,4 @@
- Three functions for working with `BuiltinArray` values:
- `listToArray` (converts a list to a `BuiltinArray`)
- `indexArray` (returns an element of a `BuiltinArray` by index)
- `lengthArray` (returns the length of a `BuiltinArray`)
- `lengthOfArray` (returns the length of a `BuiltinArray`)
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ builtinMemoryModels = BuiltinCostModelBase
, paramHeadList = Id $ ModelOneArgumentConstantCost 32
, paramTailList = Id $ ModelOneArgumentConstantCost 32
, paramNullList = Id $ ModelOneArgumentConstantCost 32
, paramLengthArray = Id $ ModelOneArgumentConstantCost 99
, paramLengthOfArray = Id $ ModelOneArgumentConstantCost 99
, paramListToArray = Id $ ModelOneArgumentConstantCost 99
, paramIndexArray = Id $ ModelTwoArgumentsConstantCost 99
, paramChooseData = Id $ ModelSixArgumentsConstantCost 32
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ builtinCostModelNames = BuiltinCostModelBase
, paramTailList = "tailListModel"
, paramNullList = "nullListModel"
, paramDropList = "dropListModel"
, paramLengthArray = "lengthArrayModel"
, paramLengthOfArray = "lengthOfArrayModel"
, paramListToArray = "listToArrayModel"
, paramIndexArray = "indexArrayModel"
, paramChooseData = "chooseDataModel"
Expand Down Expand Up @@ -214,7 +214,7 @@ createBuiltinCostModel bmfile rfile = do
paramTailList <- getParams readCF1 paramTailList
paramNullList <- getParams readCF1 paramNullList
-- Arrays
paramLengthArray <- getParams readCF1 paramLengthArray
paramLengthOfArray <- getParams readCF1 paramLengthOfArray
paramListToArray <- getParams readCF1 paramListToArray
paramIndexArray <- getParams readCF2 paramIndexArray
-- Data
Expand Down
2 changes: 1 addition & 1 deletion plutus-core/cost-model/data/builtinCostModelA.json
Original file line number Diff line number Diff line change
Expand Up @@ -698,7 +698,7 @@
"type": "constant_cost"
}
},
"lengthArray" : {
"lengthOfArray" : {
"cpu": {
"arguments": 99999999999999,
"type": "constant_cost"
Expand Down
2 changes: 1 addition & 1 deletion plutus-core/cost-model/data/builtinCostModelB.json
Original file line number Diff line number Diff line change
Expand Up @@ -698,7 +698,7 @@
"type": "constant_cost"
}
},
"lengthArray" : {
"lengthOfArray" : {
"cpu": {
"arguments": 99999999999999,
"type": "constant_cost"
Expand Down
2 changes: 1 addition & 1 deletion plutus-core/cost-model/data/builtinCostModelC.json
Original file line number Diff line number Diff line change
Expand Up @@ -707,7 +707,7 @@
"type": "constant_cost"
}
},
"lengthArray" : {
"lengthOfArray" : {
"cpu": {
"arguments": 99999999999999,
"type": "constant_cost"
Expand Down
2 changes: 0 additions & 2 deletions plutus-core/plutus-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -294,13 +294,11 @@ library
, bimap
, bytestring
, bytestring-strict-builder
, cardano-crypto >=1.2
, cardano-crypto-class ^>=2.2
, cassava
, cborg
, composition-prelude >=1.1.0.1
, containers
, crypton
, data-default-class
, deepseq
, dependent-sum >=0.7.1.0
Expand Down
39 changes: 8 additions & 31 deletions plutus-core/plutus-core/src/PlutusCore/Crypto/Ed25519.hs
Original file line number Diff line number Diff line change
@@ -1,59 +1,36 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}

module PlutusCore.Crypto.Ed25519 (
verifyEd25519Signature_V1,
verifyEd25519Signature_V2
) where
module PlutusCore.Crypto.Ed25519 (verifyEd25519Signature)
where

import PlutusCore.Builtin.KnownType (BuiltinResult)
import PlutusCore.Crypto.Utils

import Cardano.Crypto.DSIGN.Class qualified as DSIGN
import Cardano.Crypto.DSIGN.Ed25519 (Ed25519DSIGN)
import Crypto.ECC.Ed25519Donna (publicKey, signature, verify)
import Crypto.Error (CryptoFailable (..))
import Data.ByteString qualified as BS
import Data.Text (Text, pack)

-- | Ed25519 signature verification
-- This will fail if the key or the signature are not of the expected length.
-- This version uses the cardano-crypto implementation of the verification function.
verifyEd25519Signature_V1
:: BS.ByteString -- ^ Public Key (32 bytes)
-> BS.ByteString -- ^ Message (arbitrary length)
-> BS.ByteString -- ^ Signature (64 bytes)
-> BuiltinResult Bool
verifyEd25519Signature_V1 pubKey msg sig =
case verify
<$> publicKey pubKey
<*> pure msg
<*> signature sig
of CryptoPassed r -> pure r
CryptoFailed err -> failWithMessage loc $ pack (show err)
where
loc :: Text
loc = "Ed25519 signature verification"
import Data.Text (Text)

-- | Ed25519 signature verification
-- This will fail if the key or the signature are not of the expected length.
-- This version uses the cardano-crypto-class implementation of the verification
-- function (using libsodium).
verifyEd25519Signature_V2
verifyEd25519Signature
:: BS.ByteString -- ^ Public Key (32 bytes)
-> BS.ByteString -- ^ Message (arbitrary length)
-> BS.ByteString -- ^ Signature (64 bytes)
-> BuiltinResult Bool
verifyEd25519Signature_V2 pk msg sig =
verifyEd25519Signature pk msg sig =
case DSIGN.rawDeserialiseVerKeyDSIGN @Ed25519DSIGN pk of
Nothing -> failWithMessage loc "Invalid verification key."
Just pk' -> case DSIGN.rawDeserialiseSigDSIGN @Ed25519DSIGN sig of
Nothing -> failWithMessage loc "Invalid signature."
Just sig' ->
pure $
case DSIGN.verifyDSIGN () pk' msg sig' of
Left _ -> False
Right () -> True
case DSIGN.verifyDSIGN () pk' msg sig' of
Left _ -> False
Right () -> True
where
loc :: Text
loc = "Ed25519 signature verification"
26 changes: 11 additions & 15 deletions plutus-core/plutus-core/src/PlutusCore/Default/Builtins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import PlutusCore.Bitwise qualified as Bitwise
import PlutusCore.Crypto.BLS12_381.G1 qualified as BLS12_381.G1
import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2
import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing
import PlutusCore.Crypto.Ed25519 (verifyEd25519Signature_V1, verifyEd25519Signature_V2)
import PlutusCore.Crypto.Ed25519 (verifyEd25519Signature)
import PlutusCore.Crypto.ExpMod qualified as ExpMod
import PlutusCore.Crypto.Hash qualified as Hash
import PlutusCore.Crypto.Secp256k1 (verifyEcdsaSecp256k1Signature, verifySchnorrSecp256k1Signature)
Expand Down Expand Up @@ -184,7 +184,7 @@ data DefaultFun
| CaseData
| DropList
-- Arrays
| LengthArray
| LengthOfArray
| ListToArray
| IndexArray
deriving stock (Show, Eq, Ord, Enum, Bounded, Generic, Ix)
Expand Down Expand Up @@ -1340,14 +1340,10 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where
blake2b_256Denotation
(runCostingFunOneArgument . paramBlake2b_256)

toBuiltinMeaning semvar VerifyEd25519Signature =
toBuiltinMeaning _semvar VerifyEd25519Signature =
let verifyEd25519SignatureDenotation
:: BS.ByteString -> BS.ByteString -> BS.ByteString -> BuiltinResult Bool
verifyEd25519SignatureDenotation =
case semvar of
DefaultFunSemanticsVariantA -> verifyEd25519Signature_V1
DefaultFunSemanticsVariantB -> verifyEd25519Signature_V2
DefaultFunSemanticsVariantC -> verifyEd25519Signature_V2
verifyEd25519SignatureDenotation = verifyEd25519Signature
{-# INLINE verifyEd25519SignatureDenotation #-}
in makeBuiltinMeaning
verifyEd25519SignatureDenotation
Expand Down Expand Up @@ -2078,14 +2074,14 @@ instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where
dropListDenotation
(runCostingFunTwoArguments . paramDropList)

toBuiltinMeaning _semvar LengthArray =
let lengthArrayDenotation :: SomeConstant uni (Vector a) -> BuiltinResult Int
lengthArrayDenotation (SomeConstant (Some (ValueOf uni vec))) =
toBuiltinMeaning _semvar LengthOfArray =
let lengthOfArrayDenotation :: SomeConstant uni (Vector a) -> BuiltinResult Int
lengthOfArrayDenotation (SomeConstant (Some (ValueOf uni vec))) =
case uni of
DefaultUniArray _uniA -> pure $ Vector.length vec
_ -> throwing _StructuralUnliftingError "Expected an array but got something else"
{-# INLINE lengthArrayDenotation #-}
in makeBuiltinMeaning lengthArrayDenotation (runCostingFunOneArgument . unimplementedCostingFun)
{-# INLINE lengthOfArrayDenotation #-}
in makeBuiltinMeaning lengthOfArrayDenotation (runCostingFunOneArgument . unimplementedCostingFun)

toBuiltinMeaning _semvar ListToArray =
let listToArrayDenotation :: SomeConstant uni [a] -> BuiltinResult (Opaque val (Vector a))
Expand Down Expand Up @@ -2259,7 +2255,7 @@ instance Flat DefaultFun where

DropList -> 90

LengthArray -> 91
LengthOfArray -> 91
ListToArray -> 92
IndexArray -> 93

Expand Down Expand Up @@ -2355,7 +2351,7 @@ instance Flat DefaultFun where
go 88 = pure CaseList
go 89 = pure CaseData
go 90 = pure DropList
go 91 = pure LengthArray
go 91 = pure LengthOfArray
go 92 = pure ListToArray
go 93 = pure IndexArray
go t = fail $ "Failed to decode builtin tag, got: " ++ show t
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ data BuiltinCostModelBase f =
, paramTailList :: f ModelOneArgument
, paramNullList :: f ModelOneArgument
-- Arrays
, paramLengthArray :: f ModelOneArgument
, paramLengthOfArray :: f ModelOneArgument
, paramListToArray :: f ModelOneArgument
, paramIndexArray :: f ModelTwoArguments
-- Data
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -289,7 +289,7 @@ unitCostBuiltinCostModel = BuiltinCostModelBase
, paramTailList = unitCostOneArgument
, paramNullList = unitCostOneArgument
-- Arrays
, paramLengthArray = unitCostOneArgument
, paramLengthOfArray = unitCostOneArgument
, paramListToArray = unitCostOneArgument
, paramIndexArray = unitCostTwoArguments
-- Data
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ isCommutative = \case
HeadList -> False
TailList -> False
NullList -> False
LengthArray -> False
LengthOfArray -> False
ListToArray -> False
IndexArray -> False
ChooseData -> False
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -379,10 +379,10 @@ test_BuiltinArray =
let term = apply () (tyInst () (builtin () ListToArray) integer) listOfInts
typecheckEvaluateCekNoEmit def defaultBuiltinCostModelForTesting term @?=
Right (EvaluationSuccess arrayOfInts)
, testCase "lengthArray" do
, testCase "lengthOfArray" do
let arrayOfInts = mkConstant @(Vector Integer) @DefaultUni () (Vector.fromList [1..10])
let expectedLength = mkConstant @Integer @DefaultUni () 10
term = apply () (tyInst () (builtin () LengthArray) integer) arrayOfInts
term = apply () (tyInst () (builtin () LengthOfArray) integer) arrayOfInts
typecheckEvaluateCekNoEmit def defaultBuiltinCostModelForTesting term @?=
Right (EvaluationSuccess expectedLength)
, testCase "indexArray" do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -295,8 +295,8 @@ findFirstSetBit-memory-arguments
ripemd_160-cpu-arguments-intercept
ripemd_160-cpu-arguments-slope
ripemd_160-memory-arguments
lengthArray-cpu-arguments
lengthArray-memory-arguments
lengthOfArray-cpu-arguments
lengthOfArray-memory-arguments
listToArray-cpu-arguments
listToArray-memory-arguments
indexArray-cpu-arguments
Expand Down
6 changes: 3 additions & 3 deletions plutus-ledger-api/src/PlutusLedgerApi/Common/Versions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ builtinsIntroducedIn = Map.fromList [
MkPairData, MkNilData, MkNilPairData
]),
((PlutusV1, futurePV), Set.fromList [
ListToArray, IndexArray, LengthArray
ListToArray, IndexArray, LengthOfArray
]),
((PlutusV2, vasilPV), Set.fromList [
SerialiseData
Expand All @@ -114,7 +114,7 @@ builtinsIntroducedIn = Map.fromList [
IntegerToByteString, ByteStringToInteger
]),
((PlutusV2, futurePV), Set.fromList [
ListToArray, IndexArray, LengthArray
ListToArray, IndexArray, LengthOfArray
]),
((PlutusV3, changPV), Set.fromList [
Bls12_381_G1_add, Bls12_381_G1_neg, Bls12_381_G1_scalarMul,
Expand All @@ -135,7 +135,7 @@ builtinsIntroducedIn = Map.fromList [
((PlutusV3, futurePV), Set.fromList [
ExpModInteger,
CaseList, CaseData, DropList,
ListToArray, IndexArray, LengthArray
ListToArray, IndexArray, LengthOfArray
])
]

Expand Down
4 changes: 2 additions & 2 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/ParamName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -181,8 +181,8 @@ data ParamName =
| VerifyEd25519Signature'cpu'arguments'intercept
| VerifyEd25519Signature'cpu'arguments'slope
| VerifyEd25519Signature'memory'arguments
| LengthArray'cpu'arguments
| LengthArray'memory'arguments
| LengthOfArray'cpu'arguments
| LengthOfArray'memory'arguments
| ListToArray'cpu'arguments
| ListToArray'memory'arguments
| IndexArray'cpu'arguments
Expand Down
4 changes: 2 additions & 2 deletions plutus-ledger-api/src/PlutusLedgerApi/V2/ParamName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -200,8 +200,8 @@ data ParamName =
| ByteStringToInteger'cpu'arguments'c2
| ByteStringToInteger'memory'arguments'intercept
| ByteStringToInteger'memory'arguments'slope
| LengthArray'cpu'arguments
| LengthArray'memory'arguments
| LengthOfArray'cpu'arguments
| LengthOfArray'memory'arguments
| ListToArray'cpu'arguments
| ListToArray'memory'arguments
| IndexArray'cpu'arguments
Expand Down
4 changes: 2 additions & 2 deletions plutus-ledger-api/src/PlutusLedgerApi/V3/ParamName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -313,8 +313,8 @@ data ParamName =
| Ripemd_160'cpu'arguments'intercept
| Ripemd_160'cpu'arguments'slope
| Ripemd_160'memory'arguments
| LengthArray'cpu'arguments
| LengthArray'memory'arguments
| LengthOfArray'cpu'arguments
| LengthOfArray'memory'arguments
| ListToArray'cpu'arguments
| ListToArray'memory'arguments
| IndexArray'cpu'arguments
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ clearBuiltinCostModel r = r
, paramFindFirstSetBit = mempty
, paramRipemd_160 = mempty
, paramExpModInteger = mempty
, paramLengthArray = mempty
, paramLengthOfArray = mempty
, paramListToArray = mempty
, paramIndexArray = mempty
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ clearBuiltinCostModel r = r
, paramRipemd_160 = mempty
, paramExpModInteger = mempty
, paramDropList = mempty
, paramLengthArray = mempty
, paramLengthOfArray = mempty
, paramListToArray = mempty
, paramIndexArray = mempty
}
Expand Down
Loading

0 comments on commit ddfbdef

Please sign in to comment.