-
Notifications
You must be signed in to change notification settings - Fork 57
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add test scaffolding for Anoma Client
- Loading branch information
1 parent
8637618
commit 3c40bbf
Showing
13 changed files
with
437 additions
and
22 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,10 +1,13 @@ | ||
module Anoma where | ||
|
||
import Anoma.Client qualified as Client | ||
import Anoma.Compilation qualified as Compilation | ||
import Base | ||
|
||
allTests :: TestTree | ||
allTests = | ||
testGroup | ||
"Anoma tests" | ||
[Compilation.allTests] | ||
[ Compilation.allTests, | ||
Client.allTests | ||
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,7 @@ | ||
module Anoma.Client where | ||
|
||
import Anoma.Client.Positive qualified as P | ||
import Base | ||
|
||
allTests :: TestTree | ||
allTests = testGroup "Execution with the Anoma client" [P.allTests] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,47 @@ | ||
module Anoma.Client.Positive where | ||
|
||
import Anoma.Effect.Base | ||
import Base | ||
import Juvix.Compiler.Nockma.Language hiding (Path) | ||
import Juvix.Compiler.Nockma.Translation.FromTree (anomaClosure) | ||
|
||
root :: Path Abs Dir | ||
root = relToProject $(mkRelDir "tests/Anoma/Client/positive") | ||
|
||
type Check = | ||
Sem | ||
'[ Reader [Term Natural], | ||
EmbedIO | ||
] | ||
|
||
data ClientTest = ClientTest | ||
{ _clientTestNum :: Int, | ||
_clientTestTag :: Text, | ||
_clientRelRoot :: Path Rel Dir, | ||
_clientMainFile :: Path Rel File, | ||
_clientAssertion :: forall r. (Members '[Error SimpleError, Anoma, EmbedIO] r) => Term Natural -> Sem r () | ||
} | ||
|
||
makeLenses ''ClientTest | ||
|
||
clientTestName :: ClientTest -> Text | ||
clientTestName t = numberedTestName (t ^. clientTestNum) (t ^. clientTestTag) | ||
|
||
withRootCopy :: (Path Abs Dir -> IO a) -> IO a | ||
withRootCopy = withRootTmpCopy root | ||
|
||
fromClientTest :: ClientTest -> TestTree | ||
fromClientTest t = testCase (clientTestName t) assertion | ||
where | ||
assertion :: Assertion | ||
assertion = runM . runProcess . runSimpleErrorHUnit . ignoreLogger $ do | ||
res :: AnomaResult <- liftIO $ withRootCopy (compileMain False (t ^. clientRelRoot) (t ^. clientMainFile)) | ||
let program :: Term Natural = (res ^. anomaClosure) | ||
p <- envAnomaPath | ||
runAnomaEphemeral p ((t ^. clientAssertion) program) | ||
|
||
allTests :: TestTree | ||
allTests = | ||
testGroup | ||
"Anoma Client positive tests" | ||
[] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,9 @@ | ||
module Package; | ||
|
||
import PackageDescription.V2 open; | ||
|
||
package : Package := | ||
defaultPackage@{ | ||
name := "client-test"; | ||
dependencies := [defaultStdlib; path "library/"]; | ||
}; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,105 @@ | ||
--- translated from https://github.com/anoma/anoma/blob/61413dfc6460b7bf96e9207ce3b9d22b9c678f09/apps/anoma_node/lib/examples/e_transaction.ex#L309 | ||
module Swap; | ||
|
||
import Stdlib.Prelude open; | ||
import ResourceMachine open; | ||
import TransactionRequest open; | ||
import Stdlib.Debug.Trace open; | ||
import ByteArray open; | ||
|
||
trivial_true_resource_eph : Resource := | ||
mkResource@{ | ||
label := 0; | ||
logic := \{_ _ := true}; | ||
ephemeral := true; | ||
quantity := 1; | ||
data := 0; | ||
nullifier-key := replicate 32 0x0 |> mkByteArray |> toAnomaContents; | ||
rseed := 0; | ||
nonce := 0; | ||
}; | ||
|
||
trivial_true_nullifier_eph : Nat := nullifier trivial_true_resource_eph; | ||
|
||
trivial_true_eph_nullifier : Proof := | ||
let | ||
publicInputs : Public-Inputs := | ||
mkPublic-Inputs@{ | ||
commitments := []; | ||
nullifiers := [trivial_true_nullifier_eph]; | ||
self-tag := trivial_true_nullifier_eph; | ||
other-public := 0; | ||
}; | ||
privateInputs : Private-Inputs := | ||
mkPrivate-Inputs@{ | ||
committed-resources := []; | ||
nullified-resources := [trivial_true_resource_eph]; | ||
other-private := 0; | ||
}; | ||
in mkProofLogic trivial_true_resource_eph publicInputs privateInputs; | ||
|
||
trivial_true_eph_nullifier_action : Action := | ||
mkAction@{ | ||
commitments := []; | ||
nullifiers := [trivial_true_nullifier_eph]; | ||
proofs := [trivial_true_eph_nullifier]; | ||
app-data := 0; | ||
}; | ||
|
||
nullify_intent_eph : Transaction := | ||
mkTransaction@{ | ||
roots := []; | ||
delta := actionDelta trivial_true_eph_nullifier_action; | ||
actions := [trivial_true_eph_nullifier_action]; | ||
delta-proof := 0; | ||
}; | ||
|
||
trivial_true_resource : Resource := | ||
mkResource@{ | ||
label := 0; | ||
logic := \{_ _ := true}; | ||
ephemeral := true; | ||
quantity := 1; | ||
data := 0; | ||
nullifier-key := replicate 32 0x0 |> mkByteArray |> toAnomaContents; | ||
rseed := 0; | ||
nonce := 2; | ||
}; | ||
|
||
trivial_true_commitment : Proof := | ||
let | ||
true_commitment : Nat := commitment trivial_true_resource; | ||
publicInputs : Public-Inputs := | ||
mkPublic-Inputs@{ | ||
commitments := [true_commitment]; | ||
nullifiers := []; | ||
self-tag := true_commitment; | ||
other-public := 0; | ||
}; | ||
privateInputs : Private-Inputs := | ||
mkPrivate-Inputs@{ | ||
committed-resources := [trivial_true_resource]; | ||
nullified-resources := []; | ||
other-private := 0; | ||
}; | ||
in mkProofLogic trivial_true_resource publicInputs privateInputs; | ||
|
||
trivial_true_commit_action : Action := | ||
mkAction@{ | ||
commitments := [commitment trivial_true_resource]; | ||
nullifiers := []; | ||
proofs := [trivial_true_commitment]; | ||
app-data := 0; | ||
}; | ||
|
||
commit_intent : Transaction := | ||
mkTransaction@{ | ||
roots := []; | ||
delta := actionDelta trivial_true_commit_action; | ||
actions := [trivial_true_commit_action]; | ||
delta-proof := 0; | ||
}; | ||
|
||
main : TransactionRequest := | ||
TransactionRequest.fromTransaction | ||
(Transaction.compose nullify_intent_eph commit_intent); |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,47 @@ | ||
module Trivial; | ||
|
||
import Stdlib.Prelude open; | ||
import ResourceMachine open; | ||
import TransactionRequest open; | ||
|
||
logic (pub : Public-Inputs) (priv : Private-Inputs) : Bool := false; | ||
|
||
r1 : Resource := | ||
mkResource@{ | ||
label := 1; | ||
logic; | ||
ephemeral := true; | ||
data := 0; | ||
quantity := 0; | ||
nullifier-key := 0; | ||
nonce := 0; | ||
rseed := 0; | ||
}; | ||
|
||
a1 : Action := | ||
mkAction@{ | ||
commitments := []; | ||
nullifiers := []; | ||
proofs := | ||
[mkProofLogic r1 (mkPublic-Inputs [] [] 0 0) (mkPrivate-Inputs [] [] 0)]; | ||
app-data := 0; | ||
}; | ||
|
||
trivialTransaction : Transaction := | ||
mkTransaction@{ | ||
roots := []; | ||
actions := [a1]; | ||
delta := zeroDelta; | ||
delta-proof := 0; | ||
}; | ||
|
||
emptyTransaction : Transaction := | ||
mkTransaction@{ | ||
roots := []; | ||
actions := []; | ||
delta := zeroDelta; | ||
delta-proof := 0; | ||
}; | ||
|
||
main : TransactionRequest := | ||
TransactionRequest.fromTransaction emptyTransaction; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,18 @@ | ||
module ByteArray; | ||
|
||
import Stdlib.Prelude open; | ||
|
||
builtin bytearray | ||
axiom ByteArray : Type; | ||
|
||
builtin bytearray-from-list-byte | ||
axiom mkByteArray : List Byte -> ByteArray; | ||
|
||
builtin bytearray-length | ||
axiom size : ByteArray -> Nat; | ||
|
||
builtin anoma-bytearray-to-anoma-contents | ||
axiom toAnomaContents : ByteArray -> Nat; | ||
|
||
builtin anoma-bytearray-from-anoma-contents | ||
axiom fromAnomaContents : Nat -> Nat -> ByteArray; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,9 @@ | ||
module Package; | ||
|
||
import PackageDescription.V2 open; | ||
|
||
package : Package := | ||
defaultPackage@{ | ||
name := "anoma-client-library"; | ||
dependencies := [defaultStdlib]; | ||
}; |
Oops, something went wrong.