Copyright | (c) Murdoch J. Gabbay 2020 |
---|---|
License | GPL-3 |
Maintainer | murdoch.gabbay@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Haskell rendering of the mathematical idealisation of the Extended UTxO model.
Synopsis
- type Position = Atom
- data Input r = Input Position r
- data Output d v = Output Position d v
- data TransactionF f r d v = Transaction (f (Input r)) [Output d v]
- type Transaction = TransactionF []
- type Context = TransactionF NonEmpty
- class HasInputPositions a where
- inputPositions :: a -> [Position]
- class HasOutputPositions a where
- outputPositions :: a -> [Position]
- class (Support r, Support d, Support v) => Validator r d v | v -> r d where
- data ValTriv r d = ValTriv
- newtype Val r d = Val (EvFun (d, Context r d (Val r d)) Bool)
- newtype ValFin r d = ValFin (EvFinMap (d, Context r d (ValFin r d)) Bool)
- newtype Chunk r d v = Chunk {
- chunkToTxList :: Nom [Transaction r d v]
- transactionValid :: Transaction r d v -> Bool
- singletonChunk :: Transaction r d v -> Maybe (Chunk r d v)
- unsafeSingletonChunk :: HasCallStack => Transaction r d v -> Chunk r d v
- txListToChunk :: Validator r d v => [Transaction r d v] -> Maybe (Chunk r d v)
- nomTxListToNomChunk :: (HasCallStack, Validator r d v) => Nom [Transaction r d v] -> Maybe (Nom (Chunk r d v))
- nomTxListToChunk :: (HasCallStack, Validator r d v) => Nom [Transaction r d v] -> Maybe (Chunk r d v)
- exampleCh0 :: Chunk Int Int (ValTriv Int Int)
- exampleCh1 :: Nom (Chunk Int Int (ValTriv Int Int))
- exampleCh2 :: Nom (Chunk Int Int (ValTriv Int Int))
- exampleCh12 :: Chunk Int Int (ValTriv Int Int)
- exampleCh21 :: Chunk Int Int (ValTriv Int Int)
- exampleCh12' :: Maybe (Chunk Int Int (ValTriv Int Int))
- outputsOfTx :: Transaction r d v -> [Output d v]
- inputsOfTx :: Transaction r d v -> [Input r]
- txPoint :: Support r => Transaction r d v -> Position -> Context r d v
- contextsOfTx :: Support r => Transaction r d v -> [Context r d v]
- utxosOfChunk :: Validator r d v => Chunk r d v -> [Output d v]
- utxisOfChunk :: Validator r d v => Chunk r d v -> [Input r]
- contextPos :: Context r d v -> Position
- utxcsOfChunk :: Validator r d v => Chunk r d v -> Nom [Context r d v]
- appendTxChunk :: (HasCallStack, Validator r d v) => Transaction r d v -> Chunk r d v -> Maybe (Chunk r d v)
- appendTxMaybeChunk :: Validator r d v => Transaction r d v -> Maybe (Chunk r d v) -> Maybe (Chunk r d v)
- concatChunk :: Validator r d v => Chunk r d v -> Chunk r d v -> Maybe (Chunk r d v)
- safeConcatChunk :: Validator r d v => Chunk r d v -> Chunk r d v -> Maybe (Chunk r d v)
- genUnNomChunk :: Validator r d v => Chunk r d v -> Chunk r d v
- isPrefixChunk :: (UnifyPerm r, UnifyPerm d, UnifyPerm v, Validator r d v) => Nom (Chunk r d v) -> Chunk r d v -> Bool
- chunkLength :: Validator r d v => Chunk r d v -> Int
- chunkTail :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Nom (Chunk r d v))
- chunkHead :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Nom (Transaction r d v))
- warningNotChunkTail :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Chunk r d v)
- chunkTakeEnd :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Int -> Chunk r d v -> Nom (Chunk r d v)
- subTxListOf :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Nom [[Transaction r d v]]
- reverseTxsOf :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Chunk r d v)
- chunkToHdTl :: Validator r d v => Chunk r d v -> Maybe (Nom (Transaction r d v, Chunk r d v))
- chunkToHdHdTl :: Validator r d v => Chunk r d v -> Maybe (Nom (Transaction r d v, Transaction r d v, Chunk r d v))
- data Blockchain r d v
- getBlockchain :: Blockchain r d v -> Chunk r d v
- blockchain :: (HasCallStack, Validator r d v) => Chunk r d v -> Blockchain r d v
- chunkBindingOK :: Validator r d v => Chunk r d v -> Bool
- chunkValidatorsOK :: Validator r d v => Chunk r d v -> Bool
- isChunk :: Validator r d v => Chunk r d v -> Bool
- isChunk' :: (Validator r d v, UnifyPerm r, UnifyPerm d, UnifyPerm v) => Chunk r d v -> Bool
- isBlockchain :: Validator r d v => Chunk r d v -> Bool
- isBlockchain' :: Validator r d v => Maybe (Chunk r d v) -> Bool
- class IEq a
- equivChunk :: (Eq r, Eq d, IEq v, Validator r d v) => Chunk r d v -> Chunk r d v -> IO Bool
Types for inputs, outputs, and transaction lists
These are the basic types of our development.
- A
Position
is just anKAtom
(a unique identifier). It identifies a location on the blockchain. Input
s point backwards towards outputs. Inputs and outputs identify one another by position.Output
s point wait for future inputs to point to them by naming the position they carry. Outputs carry validators, to check whether they like any input that tries to point to them.- A
TransactionF
is a list of inputs (pointing backwards) and a list of outputs (pointing forwards). - A
Context
is a transaction with a distinguished designated input, i.e. an input-in-context. In fact, outputs validate contexts; this is what makes it EUTxO, for Extended UTxO, instead of just UTxO. - We also introduce the notion of
Chunk
, which is a valid list of transactions under a name-binding, and a notion of UTxI, meaning an input that does not refer to a preceding output in its chunk. - A
Blockchain
is then aChunk
with no UTxIs. The benefit of working with Chunks as primitive is that valid Chunks form a monoid and are down-closed under taking sublists.
These are all novel observations which are original to this development and the associated paper(s).
Then mathematically, the types below solve and make operational the following equations, parameterised over types r
and d
of redeemers and data:
Input = Position x r Output = d x Validator Transaction = Input-list x Output-list Context = Input-nonempty-list x Output-list Validator (d x Context) - Bool -- Val and ValFin are -- two solutions to this subset inclusion
More exposition follows in the code. See also the tests in Language.Nominal.Properties.Examples.IdealisedEUTxOSpec:
Positions are atoms. These identify locations in a Chunk
or Blockchain
.
An input has a position and a redeemer r
. Think of the redeemer is a key which we use to unlock access to whatever output this input wants to connect to.
Here r
is a type parameter, to be instantiated later.
Instances
An output has a position, a datum d
, and a validator v
.
- Think of the datum as a fragment of state data which is attached to this output.
- Think of the validator as a machine which, if given a suitable redeemer (along with other stuff), with authorise or forbid access to this output.
d
and v
are type parameters, to be instantiated later.
Instances
(Support d, Support v) => KSupport Tom (Output d v) Source # | |
(UnifyPerm d, UnifyPerm v) => KUnifyPerm Tom (Output d v) Source # | |
(Eq d, Eq v) => Eq (Output d v) Source # | |
(Ord d, Ord v) => Ord (Output d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO | |
(Show d, Show v) => Show (Output d v) Source # | |
Generic (Output d v) Source # | |
(Arbitrary d, Arbitrary v) => Arbitrary (Output d v) Source # | |
(Swappable d, Swappable v) => Swappable (Output d v) Source # | |
(Eq d, IEq v) => IEq (Output d v) Source # | Equality on validators is intensional; (Validator f == Validator f') when f and f' happen to point to the same bit of memory when the equality runs. Thus if iEq f f' returns True this means that f and f' represent the same mathematical function, and indeed are also the same code. If iEq f f' returns False this does not mean that f and f' represent distinct mathematical functions. It just means they were represented by distinct code when iEq is called. This may be useful for running tests where we check that gobs of code get put in the right places and assembled in the right ways, without necessarily caring to execute them (or even without necessarily instantiating executable values). instance IEq Value where |
HasOutputPositions (Output d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO outputPositions :: Output d v -> [Position] Source # | |
HasInputPositions (Output d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: Output d v -> [Position] Source # | |
type Rep (Output d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO type Rep (Output d v) = D1 (MetaData "Output" "Language.Nominal.Examples.IdealisedEUTxO" "nom-0.1.0.1-3UtpNOnqRlSC6EhVIia7SR" False) (C1 (MetaCons "Output" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Position) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 d) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 v)))) |
data TransactionF f r d v Source #
A TransactionF
consists of an f
of inputs, and a list of outputs.
Type parameters are:
f
a parameter which can be instantiated to a type-constructor (higher-kinded types). In this file,f
will be either list or nonempty list.r
a parameter for the redeemer.d
a parameter for the datum.v
a parameter for the validator.
Transaction (f (Input r)) [Output d v] |
Instances
type Transaction = TransactionF [] Source #
type Context = TransactionF NonEmpty Source #
Calculating input and output positions
A technical matter: we exploit the Haskell typeclass mechanisms to set up some machinery to calculate the input and output positions mentioned in a data structure. This resembles the development of
, but specialised to intputs and outputs.Support
class HasInputPositions a where Source #
A typeclass for types for which we can calculate input positions.
just traverses inputPositions
a
's type structure, looking for subtypes of the form
, and collecting the Input
p _p
s.
The only interesting instance is that of
, where bound KNom
ap
s get garbage-collected.
Nothing
inputPositions :: a -> [Position] Source #
inputPositions :: (Generic a, GHasInputPositions (Rep a)) => a -> [Position] Source #
Instances
HasInputPositions a => HasInputPositions [a] Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: [a] -> [Position] Source # | |
HasInputPositions a => HasInputPositions (NonEmpty a) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: NonEmpty a -> [Position] Source # | |
HasInputPositions (Input r) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: Input r -> [Position] Source # | |
(HasInputPositions a, HasInputPositions b) => HasInputPositions (a, b) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: (a, b) -> [Position] Source # | |
HasInputPositions (Output d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: Output d v -> [Position] Source # | |
HasInputPositions (Transaction r d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO inputPositions :: Transaction r d v -> [Position] Source # |
class HasOutputPositions a where Source #
A typeclass for types for which we can calculate output positions.
just traverses outputPositions
a
's type structure, looking for subtypes of the form
, and collecting the Output
p _ _p
s.
The only interesting instance is that of
, where bound KNom
ap
s get garbage-collected.
Nothing
outputPositions :: a -> [Position] Source #
outputPositions :: (Generic a, GHasOutputPositions (Rep a)) => a -> [Position] Source #
Instances
Validators
Our types for Output
, TransactionF
, and Context
are parameterised over a type of validators. We now build a typeclass Validator
to hold validators, and build two instances Val
and ValFin
:
Val
is just a type of functions wrapped up in a wrapper saying "I am a validator". If you have a function and it's a validator, you can put it here.ValFin
is an equivariant orbit-finite map type, intended to be used with the machinery in Language.Nominal.Equivar. A significant difference fromVal
is thatValFin
can support equalityEq
.
class (Support r, Support d, Support v) => Validator r d v | v -> r d where Source #
A typeclass for validators. A validator is an equivariant object that takes a datum and a
, and returns a Context
.Bool
A type for trivial validators that always return true
Instances
(Support r, Support d) => Validator r d (ValTriv r d) Source # | |
(Support r, Support d) => Fixable r d (ValTriv r d) Source # | |
KSupport Tom (ValTriv r d) Source # | |
KUnifyPerm Tom (ValTriv r d) Source # | |
Eq (ValTriv r d) Source # | |
Ord (ValTriv r d) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO | |
Read (ValTriv r d) Source # | |
Show (ValTriv r d) Source # | |
Arbitrary (ValTriv r d) Source # | |
Swappable (ValTriv r d) Source # | |
A ValFin
is an equivariant orbit-finite predicate on datum and context.
For convenience we make it
. Nameless
Instances
(UnifyPerm r, UnifyPerm d) => Validator r d (ValFin r d) Source # | |
(Eq r, UnifyPerm r, Eq d, UnifyPerm d) => Fixable r d (ValFin r d) Source # | |
KRestrict Tom (ValFin r d) Source # | |
KSupport Tom (ValFin r d) Source # | |
(UnifyPerm r, UnifyPerm d) => KUnifyPerm Tom (ValFin r d) Source # | |
(UnifyPerm r, UnifyPerm d) => Eq (ValFin r d) Source # | |
(Show d, Show r) => Show (ValFin r d) Source # | |
Generic (ValFin r d) Source # | |
(Eq r, UnifyPerm r, Arbitrary r, Eq d, UnifyPerm d, Arbitrary d) => Arbitrary (ValFin r d) Source # | |
Swappable (ValFin r d) Source # | |
type Rep (ValFin r d) Source # | |
Chunks
A
is a valid list of transactions in a local name-binding context.
Validity is enforced by the constructor Chunk
, which imposes a validity check.appendTxChunk
, not Chunk
, is the fundamental abstraction of our development.
A blockchain is just a chunk without any UTxIs (see Blockchain
and isBlockchain
); conversely a chunk is "like a blockchain, but may have UTxIs as well as UTxOs". utxisOfChunk
Chunks have properties that blockchains don't. For instance:
- If we slice a chunk up into pieces, we get another chunk.
- A subchunk of a chunk is still a chunk.
In contrast, if we slice up a blockchain, we get chunks, not blockchains. Thus, blockchains are not naturally compositional and structured in the way that chunks are.
This is a benefit of making the datatype of chunks our primary abstraction.
A
is a valid list of transactions in a local name-binding context. Think of it as a generalisation of blockhains that allows UTxIs (unspent transaction inputs). Chunk
Chunk | |
|
Instances
(Swappable r, Swappable d, Swappable v) => KRestrict Tom (Chunk r d v) Source # | Restrict atoms in a |
(Support r, Support d, Support v) => KSupport Tom (Chunk r d v) Source # | |
(UnifyPerm r, UnifyPerm d, UnifyPerm v) => KUnifyPerm Tom (Chunk r d v) Source # | |
Validator r d v => Semigroup (Maybe (Chunk r d v)) Source # | |
Validator r d v => Monoid (Maybe (Chunk r d v)) Source # | Maybe Chunk forms a monoid, with unit being the empty chunk. |
(UnifyPerm r, UnifyPerm d, UnifyPerm v, Validator r d v) => Eq (Chunk r d v) Source # | Chunk equality tests for equality, with permutative unification on the local names
Note: |
(Show r, Show d, Show v) => Show (Chunk r d v) Source # | |
Generic (Chunk r d v) Source # | |
(Arbitrary r, Support r, Arbitrary d, Support d, Arbitrary v, Validator r d v) => Arbitrary (Chunk r d v) Source # | |
Validator r d v => PartialMonoid (Chunk r d v) Source # | Chunk forms a partial monoid |
Defined in Language.Nominal.Examples.IdealisedEUTxO | |
Validator r d v => PartialSemigroup (Chunk r d v) Source # | |
(Swappable r, Swappable d, Swappable v) => Swappable (Chunk r d v) Source # | |
Validator r d v => Binder (Chunk r d v) [Atom] [Transaction r d v] Tom Source # | Acts on a |
type Rep (Chunk r d v) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO type Rep (Chunk r d v) = D1 (MetaData "Chunk" "Language.Nominal.Examples.IdealisedEUTxO" "nom-0.1.0.1-3UtpNOnqRlSC6EhVIia7SR" True) (C1 (MetaCons "Chunk" PrefixI True) (S1 (MetaSel (Just "chunkToTxList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Nom [Transaction r d v])))) |
transactionValid :: Transaction r d v -> Bool Source #
A
is valid if (at least) all positions are disjoint transaction
singletonChunk :: Transaction r d v -> Maybe (Chunk r d v) Source #
Tries to create a valid
from a single Chunk
. If it fails, we get TransactionF
Nothing
.
unsafeSingletonChunk :: HasCallStack => Transaction r d v -> Chunk r d v Source #
Creates a valid
from a single Chunk
.
If it fails (because the transaction is invalid), it raises an error.TransactionF
txListToChunk :: Validator r d v => [Transaction r d v] -> Maybe (Chunk r d v) Source #
nomTxListToNomChunk :: (HasCallStack, Validator r d v) => Nom [Transaction r d v] -> Maybe (Nom (Chunk r d v)) Source #
nomTxListToChunk :: (HasCallStack, Validator r d v) => Nom [Transaction r d v] -> Maybe (Chunk r d v) Source #
Combines a list of transactions in a binding context, into a Chunk, with a check that no excess positions are bound. Returns Nothing if check fails.
Examples
Some example chunks for the reader's convenience and for unit tests.
exampleCh0
is the chunk containing a trivial transaction with no inputs and no outputs (and one locally bound name, which is not used).exampleCh1
is an output with trivial validator. Wrapped in a Nom binding to store its position.exampleCh2
is an input. Wrapped in a Nom binding to store its position.exampleCh12
isexampleCh1 <> exampleCh 2
. Note their positions don't line up. Also has overbinding!exampleCh21
isexampleCh1 <> exampleCh 2
with positions lined up.exampleCh12'
isexampleCh2 <> exampleCh 1
with positions lined up. Name-clash: fails.
See isChunk
and isBlockchain
for unit tests.
exampleCh0 :: Chunk Int Int (ValTriv Int Int) Source #
Example chunk 0: "Chunk [p] [Transaction [] []]"
A chunk containing an empty transaction, with a vacuous binding by some p
.
Is chunk. Is blockchain.
>>>
isChunk exampleCh0
True
>>>
isBlockchain exampleCh0
True
exampleCh1 :: Nom (Chunk Int Int (ValTriv Int Int)) Source #
Example chunk 1: "Chunk [p] [Transaction [] [Output p 0 (const True)]]"
One output with datum 0 and trivial validator that always returns True
.
Is chunk. Is blockchain.
exampleCh2 :: Nom (Chunk Int Int (ValTriv Int Int)) Source #
Example chunk 2: "Chunk [p] [Transaction [Input p 0] []]"
One input with redeemer 0.
Is chunk. Is not blockchain.
exampleCh12 :: Chunk Int Int (ValTriv Int Int) Source #
Example chunk obtained by concatenating chunks 1 and 2. Concat succeeds but positions don't line up. Is not blockchain, and also is not valid chunk because of overbinding.
"Chunk [p1, p2] [Transaction [Input p2 0] [], Transaction [] [Output p1 0 (const True)])]"
(Note: we write lists with their head to the left, so time flows from right to left above.)
>>>
isChunk exampleCh12
False
exampleCh21 :: Chunk Int Int (ValTriv Int Int) Source #
Example chunk obtained by combining chunks 1 and 2, now on same name so input points to output.
"Chunk [p] [Transaction [Input p 0] [], Transaction [] [Output p 0 (const True)])]"
(Note: we write lists with their head to the left, so time flows from right to left above.)
Is chunk. Is blockchain.
exampleCh12' :: Maybe (Chunk Int Int (ValTriv Int Int)) Source #
Example chunk obtained by combining chunks 1 and 2, on same name. But output comes after input, not before. Concat fails because nameclash is detected.
Unspent (dangling) elements: UTxO, UTxI, UTxC
We care about which inputs point to earlier outputs, and which outputs point to later inputs, and which do not. Specifically, we introduce three functions:
, calculating those outputs that do not point to a later input in a chunk. This is standard (albeit for chunks, not blockchains).utxosOfChunk
, calculating those inputs that do not point to an earlier output in a chunk. While not complicated to define, the explicit emphasis on this as an interesting value to calculate comes from our shift from working withutxisOfChunk
Blockchain
s to working withChunk
s.
, calculating those contexts (inputs-in-their-transaction) that do not point to an earlier output in a chunk. Again, the explicit emphasis on this as an interesting value to calculate comes from our shift from working withutxcsOfChunk
Blockchain
s to working withChunk
s.
outputsOfTx :: Transaction r d v -> [Output d v] Source #
Return the output-list of a TransactionF
.
inputsOfTx :: Transaction r d v -> [Input r] Source #
Return the input-list of a TransactionF
.
txPoint :: Support r => Transaction r d v -> Position -> Context r d v Source #
Point a transaction at p
contextsOfTx :: Support r => Transaction r d v -> [Context r d v] Source #
Form the contexts of a TransactionF
.
utxosOfChunk :: Validator r d v => Chunk r d v -> [Output d v] Source #
Calculate unspent outputs.
We tell an output is unspent when its position isn't bound in the enclosing KNom
name-context.
utxisOfChunk :: Validator r d v => Chunk r d v -> [Input r] Source #
Calculate unspent inputs.
Because we're dealing with transaction lists, we care about dangling inputs (which we call UTxIs) as well as UTxOs.
contextPos :: Context r d v -> Position Source #
What's the point of my context? The position p
of the first element of the input list of a context is deemed to be the "call site" from which the context tries to find a preceding output (with position p
) in its
. Chunk
utxcsOfChunk :: Validator r d v => Chunk r d v -> Nom [Context r d v] Source #
Calculate unspent input contexts.
Because we're dealing with transaction lists, we care about dangling contexts (which we call UTxCs).
Combining and extending chunks
appendTxChunk :: (HasCallStack, Validator r d v) => Transaction r d v -> Chunk r d v -> Maybe (Chunk r d v) Source #
adds appendTxChunk
tx txstx
to txs
, provided that:
tx
is valid- there is no position name-clash and
- validators are happy.
This is the core of this file. In a certain sense, everything is just different ways of wiring into this function.
appendTxMaybeChunk :: Validator r d v => Transaction r d v -> Maybe (Chunk r d v) -> Maybe (Chunk r d v) Source #
Version of
that acts directly on appendTxChunk
Maybe (Chunk r d v)
.
concatChunk :: Validator r d v => Chunk r d v -> Chunk r d v -> Maybe (Chunk r d v) Source #
Concatenate two
s, merging their binding contexts in a capture-avoiding manner.
If concatenation is impossible (e.g. because validation fails), defaults to Chunk
Chunk Nothing
.
Note: No explicit checks are made here that inputs are valid chunks. In particular, no overbinding protection (overbinding = Nom binder in Chunk binds excess positions not involved in UTxO-UTxI linkage). If you want such checks, look at isChunk
and isBlockchain
.
Works by unpacking first chunk as a list of transactions and appending them to Just
the second argument. Local binding of first chunk gets carried over automatically; new local bindings may get generated during the append.
safeConcatChunk :: Validator r d v => Chunk r d v -> Chunk r d v -> Maybe (Chunk r d v) Source #
A version of concatChunk
that performs explicit validity checks on its inputs and result.
Splitting chunks up
isPrefixChunk :: (UnifyPerm r, UnifyPerm d, UnifyPerm v, Validator r d v) => Nom (Chunk r d v) -> Chunk r d v -> Bool Source #
chunkTail :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Nom (Chunk r d v)) Source #
chunkHead :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Nom (Transaction r d v)) Source #
Calculate the head of a chunk.
warningNotChunkTail :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Chunk r d v) Source #
Compare the code for this function with the code for
.
It looks plausible ... but it's wrong.chunkTail
It looks like it returns the tail of a chunk, and indeed it does. However, the result is not a chunk because positions get exposed.
See the test prop_warningNotChunkTail_is_not_chunk
.
chunkTakeEnd :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Int -> Chunk r d v -> Nom (Chunk r d v) Source #
subTxListOf :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Nom [[Transaction r d v]] Source #
List of subchunks.
binding is to capture dangling UTxOs or UTxIs.KNom
reverseTxsOf :: (UnifyPerm r, UnifyPerm d, Validator r d v) => Chunk r d v -> Maybe (Chunk r d v) Source #
Take a chunk and reverse its transactions. Usually this will result in an invalid chunk, in which case we get Nothing
.
Used for testing.
chunkToHdTl :: Validator r d v => Chunk r d v -> Maybe (Nom (Transaction r d v, Chunk r d v)) Source #
Split a chunk into a head and a tail.
chunkToHdHdTl :: Validator r d v => Chunk r d v -> Maybe (Nom (Transaction r d v, Transaction r d v, Chunk r d v)) Source #
Split a chunk into a head and a head and a tail.
Blockchain
data Blockchain r d v Source #
A blockchain is a valid
, with no unspent inputs.Chunk
Instances
getBlockchain :: Blockchain r d v -> Chunk r d v Source #
blockchain :: (HasCallStack, Validator r d v) => Chunk r d v -> Blockchain r d v Source #
Smart constructor for a
.
Ensures only valid blockchains are constructed, by testing for Blockchain
.isBlockchain
Is Chunk / Blockchain check
chunkBindingOK :: Validator r d v => Chunk r d v -> Bool Source #
Check that the correct atoms are bound in a Chunk
.
chunkValidatorsOK :: Validator r d v => Chunk r d v -> Bool Source #
Check that validators are happy, by taking a Chunk
apart and putting it together again.
isChunk :: Validator r d v => Chunk r d v -> Bool Source #
Is this a valid chunk? (exampleCh1
, exampleCh2
, exampleCh12
, exampleCh21
)
>>>
resAppC isChunk exampleCh1
True
>>>
resAppC isChunk exampleCh2
True
>>>
isChunk exampleCh12
False
>>>
isChunk exampleCh21
True
isChunk' :: (Validator r d v, UnifyPerm r, UnifyPerm d, UnifyPerm v) => Chunk r d v -> Bool Source #
Is this a valid chunk? Test by splitting it into a transaction list and putting it back together again.
isBlockchain :: Validator r d v => Chunk r d v -> Bool Source #
A blockchain is a valid Chunk
with no UTxI (unspent transaction inputs). (exampleCh1
, exampleCh2
, exampleCh12
, exampleCh21
)
>>>
isBlockchain exampleCh0
True
>>>
resAppC isBlockchain exampleCh1
True
>>>
resAppC isBlockchain exampleCh2
False
>>>
isBlockchain exampleCh12
False
>>>
isBlockchain exampleCh21
True
Intensional equality of Chunk
Modelled on a post by Oleg Kiselyov
An intensional equality allows us to compare Chunk
s for equality of UTxOs, even if the type of validators does not have an Eq
instance.
We don't do this at the moment (we use ValFin
instead), but we still provide the facility in case it is useful for a user running e.g. QuickCheck tests where we care that structure gets put in the right place and assembled in the right ways, without caring too much about executing that structure for values of specific interest.
Instances
IEq a => IEq [a] Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO | |
Eq r => IEq (Input r) Source # | |
IEq (a -> b) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO | |
IEq (Val r d) Source # | |
(Eq d, IEq v) => IEq (Output d v) Source # | Equality on validators is intensional; (Validator f == Validator f') when f and f' happen to point to the same bit of memory when the equality runs. Thus if iEq f f' returns True this means that f and f' represent the same mathematical function, and indeed are also the same code. If iEq f f' returns False this does not mean that f and f' represent distinct mathematical functions. It just means they were represented by distinct code when iEq is called. This may be useful for running tests where we check that gobs of code get put in the right places and assembled in the right ways, without necessarily caring to execute them (or even without necessarily instantiating executable values). instance IEq Value where |
IEq (KEvFun k a b) Source # | |
equivChunk :: (Eq r, Eq d, IEq v, Validator r d v) => Chunk r d v -> Chunk r d v -> IO Bool Source #
Intensional equality
Tests
Property-based tests are in Language.Nominal.Properties.Examples.IdealisedEUTxOSpec.