Introduction
Blockchain technology provides a way to store data and perform computations in a decentralized and untamperable way. Since the launch of Bitcoin [Nak08] blockchains had been used primarily as decentralized digital currency ledgers. Ethereum [W+14] was the first project which viewed the blockchain technology as a way to implement a decentralized and cryptographically secure transaction-based state machine, which can support arbitrary computations in the form of smart contracts. This led to the explosion of different decentralized applications, especially in the sphere of decentralized finance (DeFi) [CB20]. Nowadays, many existing blockchain platform support smart contract functionality.
With the prospect of proliferation of the Metaverse – ubuquitous virtual reality Internet – the ability to store data and make computations in the decentralized and untamperable way is of utmost importance. On the one hand, we would like the objects, documents and events which happen in the Metaverse to be (in most cases) similar to the objects, documents and events in real life: we want the objects to be unique and permanent, documents to be genuine and untamperable, and events to be final and not “rewindable”. These things are important if we would like the life in Metaverse to resemble the real life. On the other hand, any kind of centralized control of Metaverse which can ensure those properties also entails the tyrannical god-like power of the controlling organization over all lives in Metaverse. Such power can easily be abused, and therefore, a decentralized governance is of utmost importance. Blockchain technology can be used for the purposes of such governance.
One of the consequences of storing data directly in the decentralized ledger is the public availability of the data. Yet such publicity is undesirable for many possible applications, and many possible Metaverse applications require storing the data in a decentralized, verifiable, scalable and private way. Consider any internal documents of Metaverse organizations, which should not be available to the public but which should be verifiable and timestamped. Or some sort of private token which gives a user access to a private Metaverse server, and the owners of those tokens should not be disclosed to the public.
Granna project provides the privacy-preserving solution for any data records verification based on the concept of private chains — privately maintained ledgers which synchronize their block headers with the public chain to facilitate on-demand disclosure and public verification of private data. The first application of the Granna technology will be the provisioning of transparent investment funds, which work both in the Metaverse and the real world. However, the core Granna technology can be potentially applied much wider.
The key functionality of Granna system can be implemented using any public blockchain which supports smart contracts. We chose Cardano [CCM+20a, CCM+20b] as the platform for our public-chain functionality, which has recently deployed its Plutus smart contract language to the mainnet. The reasons for such choice are as follows:
Cardano is arguably the best blockchain platform among existing ones in terms of research and development quality: the theory behind the platform is based on a series of peer-reviewed research papers, formal verification methods are routinely used to check the correctness of parts of the system, and the platform’s code is written in Haskell, which is a statically typed pure functional language which is less error-prone than most other popular languages. This means that Cardano is less likely to suffer from bugs and security holes than other public blockchains.
It utilizes a proof-of-stake protocol instead of proof-of-work one, which allows running the network without significant computational costs, which, in turn, is likely to keep the transaction fees reasonably low in the future.
Unlike many other blockchains, like Ethereum or Solana, Cardano supports custom tokens natively. This means that sending custom tokens from one address requires the same fee as sending the native currency (Ada), whereas e.g. for Ethereum sending the ERC-20 token is approximately 3 times more expensive than sending ether.
It (theoretically) can issue blocks at a rate up to 1 block/second, which is faster than most popular blockchains.
It’s smart contract language, Plutus, is embedded in Haskell, and allows to define on-chain and off-chain logic together in the same module using the same datatypes. Since the existing Granna codebase is also written in Haskell, it makes the migration process much more convenient.
In this technical report, we describe the Granna functionality from a generalized perspective and then describe how such functionality can implemented on Cardano’s smart contract platform. We also give examples of interesting applications for such functionality and describe the details of public chain logic modifications required for such applications. A reader should note that even though we are focusing on Cardano integration in this report, the Granna system can be in principle use any blockhain which supports smart contract functionality as its basis.
Generalized Granna framework overview
In this section, we define the problem we are trying to solve and give a high-level overview of the Granna solution. First, let’s define some general terms.
Definition 1 (Event). Event \(e \in E\) is some arbitrary piece of data represented in bytes which have some associated time of occurence \(T(e)\). Event can represent a financial transaction, a submitted document, an event on a gaming Metaverse server, or something else.
Definition 2 (Producer). Producer \(P\) is an entity which produces a stream of events \(E_P\). Depending on the kind of events, a producer might be an investment fund manager, an admin of a Metaverse server, etc.
Definition 3 (Verifier). Verifier \(V\) is an entity which receives some set of events \(\{e_1, e_2, ... e_n\\) and wants to verify that they are genuine: that they are indeed produced by \(P\) and have happened in the stated order, and that each event \(e_k\) was indeed produced in approximately its stated time of occurence \(T(e_k)\).
The question is: how the arbitrary verifier \(V\) can verify some set of events \(E_P\) if it did not receive it directly from producer \(P\) at the time of event production?
The easiest solution is some centralized trusted third party \(C\): all producers \(P_1, P_2 .. P_n\) send events to \(C\) as they are produced, and all verifiers \(V_1, V_2 .. V_m\) query \(C\) to verify it. But relying on trust always creates problems: a centralized third party can be hacked or otherwise corrupted, allowing the adversary to change the global events log as they please (e.g. if \(P\) is Metaverse server where an influential person abuses other players, and \(C\) is a centralized Metaverse logging system for player’s interactions, this influential person can change the logs in \(C\) and claim that the original data provided by administrators of server \(P\) is fake).
Blockchain allows for storing any kind of data as part of transactions in the decentralized ledger. Therefore, we can do the same but in a decentralized way: all producers send events to a public blockchain as parts of consecutive transactions, and any verifier \(V\) can simply look up the events in the public ledger and check if the transactions which contain them are signed by the Producer’s public key. The main problem with that solution is that events are fully public, which is unacceptable for some sorts of events, like internal documents of organizations, which should only be accessible by the organization, its employees and (possibly) some third-party auditors. Another problem is that the actual event data can be very large, e.g. if events are video segments, and including them will make the blockchain transaction very slow and expensive to process.
We can fix both the problem of privacy and the problem of variable event size by sending hashes of events to the blockchain instead of events themselves, using a predefined cryptographic hash function \(H\). This solution works, since every verifier \(V\) can match a set of events \(\{e_1, ... e_k\}\) with the corresponding set of hashes \(\{H(e_1), ... H(e_k)\}\) published and signed by \(P\) on the blockchain, and thus make sure that those events were indeed available to the producer at the times of corresponding transactions. At the same time, the amount of data stored in the events themselves does not matter, since \(size(H(e)) = const\) for every \(e\).
However, this solution still has the problem of scalability. Each transaction in the public blockchain is associated with a transaction fee, and throughput of most public chains currently does not exceed 10-20 transactions per second (TPS). What if a producer wants to submit lots of concurrently happening events, each of which a verifier might need to validate separately? An example is a large Metaverse server with a million players which keeps the private logs of all player interactions, and only one such event is necessary to be presented as evidence of abuse. An average public blockchain will not be able to handle a million TPS coming from one such producer. Or what if a producer does not actually care if its events are available for verification exactly at the time they appear, but deems it too expensive to pay a transaction fee for every event produced?
Granna solves these problems by allowing the producers to bundle the events into private blocks, thus forming a private chain of events, and submitting only the headers of the private blocks to private chains while still allowing individual events to be verified without requiring access to all other events in the block. The result is a flexible system which allows the producers to trade off the precision of verifiable temporal localization of the events with the number of those events and the cost of interoperating with the public chain. Next subsections describe how it is done in more detail.
Off-chain logic (private chains)
A private block has similar structure to the public chain block in most current blockchain platforms: it is a Merkle tree constructed over the list of events. We use the modification of the Merkle tree which includes its size and the sizes of its subtrees in the node hash computation (Fig. 1). This is useful for some potential applications, i.e. if we want to charge the Producer a fee which depends on the number of events made available for verification. An event \(e_k\) can be verified against the tree root if the Merkle path from the root to \(e_k\) is provided including the sibling nodes of non-leaf nodes on the path. A verifier can then recalculate the hashes along the path and make sure that the resulting tree root hash is equal to the given one.
A Granna proof of a set of events \(\{e_1 ... e_k\}\) is then a set of corresponding Merkle paths \(\{path(e_1) ... path(e_k)\}\), where each path ends with a private block hash and for each private block the ID of the transaction containing its header in the public chain is also provided. If some of the events belong to the same private block, their corresponding paths can then be combined into Merkle subtrees (Fig. 2). A verifier which has the set of events with corresponding proofs can then verify that they are genuine by checking the correctness of proofs themselves (recalculating the hashes in the Merkle subtrees and making sure that they match with the given ones), checking the existence of corresponding transactions in the public chain, verifying that the transactions were signed by the Producer and matching the proof headers with headers contained in the transactions.
The Granna proof can also contain multiple consecutive private block headers which are linked to each other (Fig. 2). If that is the case, it is sufficient to only query a single transaction in the public chain – the one which contains the last private block header in the sequence. Since all the other block headers are linked to the last one, they then can be treated as ordinary intermediate nodes in the large single Merkle tree and be recalculated and checked in the same way. This allows for producing proofs for arbitrarily large subsets of events, which can be verified using only single query to the public chain network.
On-chain logic (public chain)
On-chain logic makes sure that the private block headers sent by the Producer form a continuous chain. It does so by checking that in each new transaction from the Producer which contains a private block header, this header refers to a previous block submitted by the same producer; or, in case if the Producer submits a first block, it performs some additional actions like charging a special fee from Producer.
Another part of what can be considered an “on-chain logic” is the verification of the proofs against the block header. However, this logic is trivial and does not require sending any transactions to the network or spending gas fees, since it is a read-only operation on the chain – transactions are only fetched. This means that verification of the proof is a quick and free operation.
Translating to Cardano ledger model
Overview of Extended Multi-asset UTxO model
We can implement the on-chain logic described above on Cardano using its support of native custom tokens and validator scripts which are formalized in the \(\mathrm{EUTXO}_{ma}\) model [CCM+20b]. Like in standard UTxO model (used by Bitcoin) and unlike in account-based model (like in Ethereum), wallet addresses in \(\mathrm{EUTXO}_{ma}\) do not have the account balance as an intrinsic property, but instead balance is the sum of values of unspent transaction outputs. Unlike in Bitcoin, the value of the output is not a single number (amount of money), but rather a nested map of values, e.g. \(v = \{ \text{Coin} \rightarrow \{ \text{Coin} \rightarrow 5 \} , g \rightarrow \{ foo \rightarrow 3, bar \rightarrow 1 \} \}\). This is how native tokens are implemented in Cardano — in this example, the value map holds 2 currencies: the main currency \(\text{Coin}\) with the only token type \(\text{Coin}\) (which corresponds to Ada for Cardano), and custom currency \(g\) with two token types \(foo\) and \(bar\).
A transaction in this model is a sextuple \((I, O, r, mint, mpss, S)\), where \(I\) is a set of references to outputs spent by that transaction, \(O\) is a list of outputs produced, \(r\) is a transaction validity interval, \(mint\) is a value minted by transaction, \(mpss\) is the set of minting policies stored in the transaction, and \(S\) is a set of signatures. \(mint\) and \(mpss\) parts of the transaction provide the functionality of minting custom tokens: \(mint\) defines which currencies with which token names should be minted, and \(mpss\) contains Plutus scripts which verify if minting of such value is allowed for each of the currency symbols.
Smart contracts in Cardano are implemented as validator scripts associated with particular unspent transaction outputs. A hash of the validator script \(\nu\) is its address; each output send to this address has to be validated with it. Each output owned by a scriptnetwork-httpnetwork-http address is a triple \((\nu, value, \delta)\), where \(\nu\) is a serialized validator script itself, \(value\) is the token value map as described before, and \(\delta\) is a datum — an additional piece of auxiliary data. This output can be spend only if \(\nu(\rho, \delta, \sigma) = \mathrm{true}\) holds, where \(\rho\) is the additional piece of data for authentication, called the redeemer (e.g. a digital signature), and \(\sigma\) is the entire transaction which is spending the output, including all its inputs and new outputs. Since the validator script has access to the entirety of the transaction, it can, for example, make sure that the spend tokens (or some of them) stay in the contract, or that some fee in custom tokens is paid to contract as a part of transaction.
As we can see, the contracts in Cardano are unlike contracts in most other blockchains, because they are pure functions — they do not have any internal state, they are just predicates which tell whether or not the given transaction is valid. How then any non-trivial logic can be implemented in such contracts? The answer is that we can simulate the stateful contract in this model using the datum \(\delta\), which is a part of every contract address output. The datum represents the contract state, and the validator script makes sure that:
Every transaction which spends the contract output containing the datum should create a new output with a modified datum on the contract address;
The modification of the datum was done accordingly to the rules.
This way, the actual modification of the contract state is delegated to off-chain logic, while on-chain validator only checks if the transaction constructed by the on-chain code do not break the rules of the contract. This makes the on-chain logic simpler and faster in most cases and offloads the bulk of the contract computation to the client. Using this approach, many useful stateful contracts like \(n\)-of-\(m\) multi-signature payment contract can be implemented (Fig. 3).
However, since the validator only controls the transactions which spend the script’s output, it cannot control the transactions which create new outputs on the script address. Since the client can provide any datum for such new output, it means that anybody can create a state machine instance in the middle of the execution out of thin air. To prevent this, Cardano offers a mechanism of state thread tokens. State thread token is a non-fungible tokens (NFT) which can be minted only once on contract initialization, and should spent and re-sent to the contract by every transaction which uses the NFT. This way the continuity of the state machine is ensured. In Cardano, NFT are implemented via a one-shot minting policy – a policy which requires the transaction minting the token to spend a particular UTXO. Since the given UTXO can be spent only once, the minting policy can be run only once, hence the minted tokens will be unique.
Using this state machine abstraction, we can build the core functionality of Granna – accepting and validating private block headers – in a straightforward and an extensible way.
Granna core functionality implemented in Extended Multi-asset UTxO
A lifecycle of a public chain instance of Granna smart contract goes on like this:
A producer \(P\) creates an initial transaction which does two things:
It mints a unique thread token (NFT) \(g_P\) which is associated with the minting policy \(\phi_{g_P}\). \(\phi_{g_P}\) is a one-shot minting policy: it only mints 1 token with ticker “GRNN” if the particular UTxO (provided by producer on the token creation) is contained in the inputs of initial transaction.
It sends a newly created token to the address of Granna smart contract, adding a private genesis block header and its own public key :math:`pk_P` as a datum to the transaction. A private genesis block header is two hashes which can be hashes of any random value.
Each next transaction from the producer should then spend the script address output which contains the produced NFT. The Granna contract (which is the output’s validator) checks the following:
The spending transaction is signed by the owner of the public key present in the datum of the spent output;
The spending transaction sends the spent NFT token back to contract’s address;
The transaction’s output which contains the re-sent NFT also contains a datum with a private block header and a public key, such as:
A private block header correctly refers to the previous block header stored in the datum of the spent output;
A public key matches the signer of the transaction.
This logic can be represented as a state machine on Fig. 4. This way, the Granna contract accumulates on its address a number of NFTs, each associated with different with different producer \(P\). Each transaction from the contract to itself represents a new private block issued by some particular producer. A verifier \(V\) which has some set of events with proofs only has to fetch the transactions referred by transaction IDs included in the proofs, make sure that they from the contract to itself and that they indeed contain the public key of \(P\) and private block headers equal to ones provided in proofs.
Plutus contract implementation
An experimental implementation of the logic above in Plutus is as follows:
import Control.Monad hiding (fmap)
import Data.Aeson (FromJSON, ToJSON)
import qualified Data.Map as Map
import Data.Monoid (Last (..))
import Data.Text (Text)
import GHC.Generics (Generic)
import Ledger hiding (singleton)
import Ledger.Tx
import Plutus.ChainIndex.Tx (ChainIndexTx (..))
import Plutus.Contract as Contract
import qualified PlutusTx
import qualified PlutusTx.Builtins as Builtins
import PlutusTx.Prelude hiding (Semigroup (..), unless)
-- import Ledger.Contexts
import Ledger.Ada as Ada
import Ledger.Constraints as Constraints
import Ledger.Scripts (validatorHash)
import qualified Ledger.Typed.Scripts as Scripts
import Ledger.Value as Value
-- import Plutus.Contracts.Currency as Currency
import Prelude (Semigroup (..), Show (..), String)
import qualified Prelude as Haskell
import Plutus.Trace.Emulator (EmulatorTrace)
import qualified Plutus.Trace.Emulator as Trace
import Plutus.Contract.Trace as X
{-
General datatypes and functions
-}
data PrivateBlockHeader = PrivateBlockHeader
{ prevBlockHash :: !BuiltinByteString
, merkleRoot :: !BuiltinByteString
} deriving stock (Generic, Haskell.Show, Haskell.Eq)
PlutusTx.makeLift ''PrivateBlockHeader
PlutusTx.unstableMakeIsData ''PrivateBlockHeader
{-
Validator script
-}
data GrannaDatum = GrannaDatum
{ privBlockHeader :: !PrivateBlockHeader
, threadOwner :: !PubKeyHash
} deriving stock (Generic, Haskell.Show, Haskell.Eq)
PlutusTx.makeLift ''GrannaDatum
PlutusTx.unstableMakeIsData ''GrannaDatum
data Granna
instance Scripts.ValidatorTypes Granna where
type instance DatumType Granna = GrannaDatum
type instance RedeemerType Granna = ()
{-# INLINABLE headerHash #-}
headerHash :: PrivateBlockHeader -> BuiltinByteString
headerHash (PrivateBlockHeader pbh mr) = sha2_256 $ Builtins.appendByteString pbh mr
{-# INLINABLE valsSentToScript #-}
valsSentToScript :: ValidatorHash -> TxInfo -> Maybe (GrannaDatum, Value)
valsSentToScript valHash txinfo = do
(dHash, val) <- listToMaybe $ scriptOutputsAt valHash txinfo
datum <- findDatum dHash txinfo
typedDatum <- PlutusTx.fromBuiltinData $ getDatum datum
return (typedDatum, val)
{-# INLINABLE grannaValidatorFunc #-}
grannaValidatorFunc :: GrannaDatum -> () -> ScriptContext -> Bool
grannaValidatorFunc prevDatum _ ctx@ScriptContext{scriptContextTxInfo=txinfo} =
let
valHash = ownHash ctx
origOwner = threadOwner prevDatum
prevHeaderHash = headerHash $ privBlockHeader prevDatum
spentByOwner =
let v = txSignedBy txinfo origOwner
in traceIfFalse "Spender does not own the chain thread" v
continuesChainCorrectly = fromMaybe False $ do
prevValue <- txOutValue . txInInfoResolved <$> findOwnInput ctx
(nextDatum, nextValue) <- valsSentToScript valHash txinfo
let nextPbh = prevBlockHash $ privBlockHeader nextDatum
nextOwner = threadOwner nextDatum
resendsSameToken =
traceIfFalse "NFT does not go back to contract" $ prevValue == nextValue
continuesBlockChain =
traceIfFalse "Invalid previous block header hash" $ prevHeaderHash == nextPbh
sameOwner =
traceIfFalse "Attempt to change private chain owner" $ origOwner == nextOwner
return $ resendsSameToken && continuesBlockChain && sameOwner
in spentByOwner && continuesChainCorrectly
typedGrannaValidator :: Scripts.TypedValidator Granna
typedGrannaValidator = Scripts.mkTypedValidator @Granna
$$(PlutusTx.compile [|| grannaValidatorFunc ||])
$$(PlutusTx.compile [|| wrap ||])
where
wrap = Scripts.wrapValidator @GrannaDatum @()
grannaValidator :: Scripts.Validator
grannaValidator = Scripts.validatorScript typedGrannaValidator
grannaHash :: ValidatorHash
grannaHash = validatorHash grannaValidator
grannaAddress :: Address
grannaAddress = scriptAddress grannaValidator
{-
NFT minting policy
-}
data DscpThreadCurrency = DscpThreadCurrency
{ dtcSpentOutput :: (TxId, Integer)
, dtcContractHash :: ValidatorHash
} deriving stock (Generic, Haskell.Show, Haskell.Eq)
PlutusTx.makeLift ''DscpThreadCurrency
mkDscpThread :: TxOutRef -> DscpThreadCurrency
mkDscpThread (TxOutRef h i) = DscpThreadCurrency (h, i) grannaHash
{-# INLINABLE dscpTokenName #-}
dscpTokenName :: TokenName
dscpTokenName = TokenName "GRNN"
{-# INLINABLE mkPolicy #-}
mkPolicy :: DscpThreadCurrency -> () -> ScriptContext -> Bool
mkPolicy dtc _ ctx@ScriptContext{scriptContextTxInfo=txinfo} =
let
(h, i) = dtcSpentOutput dtc
valHash = dtcContractHash dtc
spendsTxOut =
let v = spendsOutput txinfo h i
in traceIfFalse "Pending transaction does not spend a designated output" v
ownSymbol = ownCurrencySymbol ctx
minted = txInfoMint txinfo
expected = Value.singleton ownSymbol dscpTokenName 1
mintsToken =
let v = expected == minted
in traceIfFalse "Invalid minted value" v
sendsCorrectlyToScript =
let v = case valsSentToScript valHash txinfo of
Nothing -> False
Just (GrannaDatum {..}, val) ->
txSignedBy txinfo threadOwner && -- it's signed by the owner of pubkey in the datum
val == expected -- it sends the token just minted to the script
in traceIfFalse "Minted token with correct data is not sent to Granna script" v
in spendsTxOut && mintsToken && sendsCorrectlyToScript
policy :: DscpThreadCurrency -> Scripts.MintingPolicy
policy dtc = mkMintingPolicyScript $
$$(PlutusTx.compile [|| Scripts.wrapMintingPolicy . mkPolicy ||])
`PlutusTx.applyCode`
PlutusTx.liftCode dtc
curSymbol :: DscpThreadCurrency -> CurrencySymbol
curSymbol = scriptCurrencySymbol . policy
{-
Off-chain code
-}
type GrannaSchema =
Endpoint "startChain" ()
.\/ Endpoint "submitBlock" BuiltinByteString
.\/ Endpoint "validateHeader" (TxId, BuiltinByteString)
startChain :: Promise () GrannaSchema Text ()
startChain = endpoint @"startChain" $ \_ -> do
pkHash <- Contract.ownPubKeyHash
utxos <- utxosAt $ pubKeyHashAddress pkHash
case Map.keys utxos of
[] -> Contract.logError @String "no utxo found"
oref : _ -> do
let dtc = mkDscpThread oref
val = Value.singleton (curSymbol dtc) dscpTokenName 1
genHead = PrivateBlockHeader "" ""
datum = GrannaDatum genHead pkHash
lookups = Constraints.mintingPolicy (policy dtc) <>
Constraints.typedValidatorLookups typedGrannaValidator <>
Constraints.unspentOutputs utxos
tx = Constraints.mustMintValue val <>
Constraints.mustSpendPubKeyOutput oref <>
Constraints.mustPayToTheScript datum val
ledgerTx <- submitTxConstraintsWith @Granna lookups tx
void $ awaitTxConfirmed $ getCardanoTxId ledgerTx
submitBlock :: Promise () GrannaSchema Text ()
submitBlock = endpoint @"submitBlock" $ \mrkRoot -> do
pkHash <- Contract.ownPubKeyHash
scriptUtxos <- utxosAt grannaAddress
case Map.assocs scriptUtxos of
-- TBD This is a toy example which assumes that there is only one producer;
-- real off-chain code will not assume that and will instead remember
-- the last UTxO from the private chain in the application memory
[(oref, ScriptChainIndexTxOut { _ciTxOutDatum = (Right rawDatum), _ciTxOutValue = val })] ->
let GrannaDatum{privBlockHeader=pbh} =
fromMaybe (error ()) $
PlutusTx.fromBuiltinData $ getDatum rawDatum
prevBlockHash = headerHash pbh
newHead = PrivateBlockHeader
{ prevBlockHash = prevBlockHash
, merkleRoot = mrkRoot
}
newDatum = GrannaDatum newHead pkHash
tx = Contract.collectFromScript scriptUtxos () <>
Constraints.mustPayToTheScript newDatum val
in do
ledgerTx <- submitTxConstraintsSpending typedGrannaValidator scriptUtxos tx
void $ awaitTxConfirmed $ getCardanoTxId ledgerTx
_ -> Contract.logError @String "script address has no valid utxo"
validateHeader :: Promise () GrannaSchema Text ()
validateHeader = endpoint @"validateHeader" $ \(txid, mrkRoot) -> txFromTxId txid >>= \case
Nothing ->
Contract.logError @String "INVALID: no transaction found"
Just ChainIndexTx{_citxData=datums} -> do
let (rawDatum:_) = Map.elems datums
GrannaDatum{privBlockHeader=pbh} =
fromMaybe (error ()) $
PlutusTx.fromBuiltinData $ getDatum rawDatum
if mrkRoot == merkleRoot pbh
then Contract.logInfo @String "VALID: all good"
else Contract.logError @String $ "INVALID: bad merkle root, expected " ++ show (merkleRoot pbh) ++ ", got " ++ show mrkRoot
endpoints :: Contract () GrannaSchema Text ()
endpoints = selectList [startChain, submitBlock, validateHeader] >> endpoints
Transparent investment funds based on Granna
Motivation
A primary application of focus for Granna is the building of transparent exchange-traded private investment funds with active management which lie in-between the classic financial markets and decentralized financial markets of Metaverse. The main purpose of Granna in this setting would be to provide methods for transparent semi-automatic auditing of the funds’ results and the performance.
The abstract events we described in the previous parts become the crucial documents which describe the development of the fund’s assets and investment strategy over the period of time, such as:
Analytics reports
Investment strategy plans
Fund performance reports, etc.
This data should not usually be available to the general public until the fund publishes its annual/quarterly report, since they disclose the details of the funds’ investment strategy. The problem with the investment funds is that fund managers might not be honest when reporting the fund’s performance and therefore the shareholders might not receive the full amount of income they are entitled to. In the world of classical finance, this problem is “solved” by trusting in the investment fund reputation and the laws which hold the fund’s managers responsible for misrepresenting the fund’s performance.
The evidence for fraud can be obtained by SEC during the process of fund’s annual audit. However, this process is tedious and highly centralized, and there is still room for the manipulation in the report.
Using Granna technology, however, each significant step in the fund’s development can be fixed against a public blockchain without disclosing it prematurely. Each internal report and investment decision during the financial year can be treated as a verifiable event and included into the investment fund’s private chain. When this information is disclosed at the audit time, there is much less room for fraud, since each document is tied to the private block header which was issued shortly after the moment the document was actually created. This way, it is much harder to present fraudulent information about the fund’s operation at the time of audit, since the documents accumulated over the whole period of fund operation cannot be tampered.
This by itself is a good application of Granna technology, but how would Granna automate the process of investment further in a decentralized way? In fact, the entirety of the investment process can be automated using smart contracts. We would like to allow investors on the blockchain to do the following:
Automatically buy the fund’s shares for a fungible token;
Trade the fund shares on the secondary market as the fund operates;
Vote on the approval of the fund’s audit in a decentralized way;
Redeem the shares and reap the profits accordingly to the audited fund’s performance.
In order to do so, we need to extend the basic Granna functionality with several components:
A fungible Granna Investment Token (GRNN);
Fund-specific fungible share tokens, which represent the shares of the particular fund and are minted at the creation of the fund;
A multi-party approval mechanism which governs the process of redeeming the share tokens.
Granna investment fund contract logic
The lifecycle of Granna investment fund operation then proceeds as follows:
The producer (investment fund manager) creates the first transaction which does the following:
In addition to initializing the state thread token of fund’s contract, the initial transaction also mints a number of share tokens. These tokens have the same currency symbol as state thread token, but have a different token name and there are many of them. The state thread token and share tokens are going into different transaction outputs.
The genesis private block header produced by this initial transaction can also contain a hash of the document describing the fund’s goals and initial strategy instead of a random hash. The document itself can be provided off-chain, e.g. using an IPFS link included in the transaction’s datum.
The initial transaction also declares the price of one share in terms of Granna Investment Tokens (GRNN), denoted as \(C\), and the funding stage deadline \(d_F\), expressed as the slot number (a number of timesteps passed since the blockchain start in Cardano). Those are included in the datums of all the transaction’s outputs.
It also declares the minimum amount of investment \(M\) which is required for the fund’s operation to commence, and the audit and redeeming deadline \(d_A\), that is the slot number which contains the Those are stored in the datum of the output which contains a state thread token.
The potential shareholders can then automatically acquire the shares for the GRNN tokens they hold by the price listed by the fund manager (which is stored in the datums of the outputs which hold the share tokens). A validator script checks that:
The number of GRNN tokens provided in the inputs of buyer’s transaction is equal to the \(C \cdot N\), where N is the number of shares bought (which is number of shares in the inputs minus number of shares returning to the contract address in the outputs);
All the GRNN tokens in the transaction are put onto the Granna contract address;
The current slot number is less than funding deadline \(d_F\).
The producer can proceed with adding private chain headers to the contract if and only if:
The transaction which spends the state thread token also spends \(M\) GRNN tokens residing on the contract address in total; this way, it ensures that a fund does not start working until sufficient funding is obtained.
The collected GRNN tokens are redirected back to the contract in the same output as state thread token;
The current slot does not exceed the audit and redeeming deadline \(d_A\)
If the fund did not collect the necessary investments until the funding deadline \(d_F\), the GRNN tokens held in the contract can then be redeemed back for share tokens at the same price.
Producer adds private block headers to the contract until the redeeming deadline slot \(d_A\) is reached. After that, the producer can only switch the state of the contract to audit state. The transaction which does that should also:
Declare the profit margin obtained on the investments \(\alpha\);
Lock the additional funds in the output which correspond to the declared profit margin (either in GRNN tokens or the native currency (Ada));
Contain a resource (i.e. an IPFS link) which allows everyone to download the fund’s internal documentation and performance reports with the corresponding Granna proofs which connect to the private block headers previously published by the fund.
On the audit stage, the holders of the share tokens can vote on the validity of the declared profit margin by sending transactions which:
Contain a number of share tokens in their inputs and outputs (they do not need to be put on the contract address, just be present in the transaction);
Adds the number of votes which is equal to the number of shares in the transaction to the number of “APPROVE” or “DECLINE” votes, which are stored in the contract datum and are initially zero.
If the number of “APPROVE” votes exceeds the half of number of shares in the fund, the contract switches to redeeming stage:
The shareholders can claim their staked GRNN tokens including the profit margin back from the contract in exchange for the share tokens.
The fund can then proceed to the next operational cycle by repeating the funding stage. Note that it does not require that all the shareholders redeem their shares on the previous stage: the stakeholders can hold onto the fund shares and wait while they would grow in price as the fund further increases its revenue.
If the number of “DECLINE” votes exceeeds the half of number of shares, the contract address switches to default stage, where the shareholders can claim their GRNN tokens back similarly to redeeming stage, but the fund cannot proceed with further operations and the contract cannot move to a different state anymore.
It is important to note that share tokens are the same as any other tokens and therefore they can be traded on the secondary market, e.g. on the decentralized exchange platform.
Third-party auditors
It is important to note that auditing the fund’s reports, even if the times of production of each particular document and the document’s originality are ensured by Granna proof. The contents of the documents should also be analyzed to ensure that the proposed profit margin is legitimate. It is not very realistic to assume that every minor shareholder will take the time to analyze the contents of the reports; it is possible that many shareholders will choose to cast the approving vote automatically to save time, which will devalue the votes as a mechanism of ensuring the fund’s accountability. To address this issue, we propose the mechanism of third-party audit delegation, implemented as a separate contract. This contract should be able to:
Accept the share tokens from the shareholders with a small fee and lock them on the contract address;
Only support the withdrawal of the shares from the contract address via a batch voting transaction, which does the following:
Spends the share tokens put on the contract address by the stakeholders;
Ensures that all the share token outputs are provided with an acceptable fee, which is redirected to the address of the audit contract owner;
Casts the number of votes equal to the total number of shares delegated on the Granna fund contract;
Returns each share to its original owner (the address which submitted the share to the contract).
Since this way all the voting transactions get batched into few large transactions, the total transaction fees spent on running the Granna validator script for each vote are greatly reduced. Therefore, it might be even profitable for shareholders to use the services of an independent auditor. The auditors themselves can provide the audits of many different funds and build their reputation in this way, attracting more shareholders and thus making more money.
- CCM+20a
Manuel MT Chakravarty, James Chapman, Kenneth MacKenzie, Orestis Melkonian, Michael Peyton Jones, and Philip Wadler. The extended utxo model. In International Conference on Financial Cryptography and Data Security, 525–539. Springer, 2020.
- CCM+20b(1,2)
Manuel MT Chakravarty, James Chapman, Kenneth MacKenzie, Orestis Melkonian, Jann Müller, Michael Peyton Jones, Polina Vinogradova, and Philip Wadler. Native custom tokens in the extended utxo model. In International Symposium on Leveraging Applications of Formal Methods, 89–111. Springer, 2020.
- CB20
Yan Chen and Cristiano Bellavitis. Blockchain disruption and decentralized finance: the rise of decentralized business models. Journal of Business Venturing Insights, 13:e00151, 2020.
- Nak08
Satoshi Nakamoto. Bitcoin: a peer-to-peer electronic cash system. Decentralized Business Review, pages 21260, 2008.
- W+14
Gavin Wood and others. Ethereum: a secure decentralised generalised transaction ledger. Ethereum project yellow paper, 151(2014):1–32, 2014.