Skip to content

Commit

Permalink
Implement 'decodeTxId' / FromJSON (GenTxId (CardanoBlock crypto))
Browse files Browse the repository at this point in the history
  This assumes the transaction id to be base16-encoded, which is consistent with the rest of the API.
  • Loading branch information
KtorZ committed Jan 17, 2022
1 parent 09eac21 commit 655e569
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 3 deletions.
22 changes: 21 additions & 1 deletion server/src/Ogmios/Data/Json.hs
Expand Up @@ -30,20 +30,23 @@ module Ogmios.Data.Json
, decodePoint
, decodeSubmitTxPayload
, decodeTip
, decodeTxId
) where

import Ogmios.Data.Json.Prelude

import Cardano.Binary
( FromCBOR (..), ToCBOR (..) )
import Cardano.Crypto.Hash
( hashFromBytes )
import Cardano.Crypto.Hashing
( decodeHash, hashToBytes )
import Cardano.Ledger.Crypto
( Crypto )
import Cardano.Ledger.Shelley.API
( ApplyTxError (..), PraosCrypto )
import Cardano.Network.Protocol.NodeToClient
( SubmitTxError, SubmitTxPayload )
( GenTx, GenTxId, SubmitTxError, SubmitTxPayload )
import Cardano.Slotting.Block
( BlockNo (..) )
import Cardano.Slotting.Slot
Expand All @@ -60,20 +63,25 @@ import Ouroboros.Consensus.Cardano.Block
, GenTx (..)
, HardForkApplyTxErr (..)
, HardForkBlock (..)
, TxId (GenTxIdAlonzo)
)
import Ouroboros.Consensus.HardFork.Combinator
( OneEraHash (..) )
import Ouroboros.Consensus.Shelley.Eras
( MaryEra )
import Ouroboros.Consensus.Shelley.Ledger
( ShelleyBlock )
import Ouroboros.Consensus.Shelley.Ledger.Mempool
( TxId (..) )
import Ouroboros.Network.Block
( Point (..), Tip (..), genesisPoint, wrapCBORinCBOR )
import Ouroboros.Network.Point
( Block (..) )
import Ouroboros.Network.Protocol.LocalStateQuery.Type
( AcquireFailure (..) )

import qualified Cardano.Ledger.SafeHash as Ledger
import qualified Cardano.Ledger.TxIn as Ledger
import qualified Codec.CBOR.Encoding as Cbor
import qualified Codec.CBOR.Read as Cbor
import qualified Codec.CBOR.Write as Cbor
Expand Down Expand Up @@ -261,3 +269,15 @@ decodeTip json =
hash <- obj .: "hash" >>= decodeOneEraHash
blockNo <- obj .: "blockNo"
pure $ Tip (SlotNo slot) hash (BlockNo blockNo)

decodeTxId
:: forall crypto. PraosCrypto crypto
=> Json.Value
-> Json.Parser (GenTxId (CardanoBlock crypto))
decodeTxId = Json.withText "TxId" $ \(encodeUtf8 -> utf8) -> do
bytes <- decodeBase16 utf8
case hashFromBytes bytes of
Nothing ->
fail "couldn't interpret bytes as blake2b-256 digest."
Just h ->
pure $ GenTxIdAlonzo $ ShelleyTxId $ Ledger.TxId (Ledger.unsafeMakeSafeHash h)
5 changes: 3 additions & 2 deletions server/src/Ogmios/Data/Json/Orphans.hs
Expand Up @@ -20,6 +20,7 @@ import Ogmios.Data.Json
( decodePoint
, decodeSubmitTxPayload
, decodeTip
, decodeTxId
, encodeSubmitTxError
, encodeSubmitTxPayload
, encodeTip
Expand Down Expand Up @@ -64,8 +65,8 @@ instance ToJSON (Point (CardanoBlock crypto)) where
instance PraosCrypto crypto => FromJSON (GenTx (CardanoBlock crypto)) where
parseJSON = decodeSubmitTxPayload

instance FromJSON (GenTxId (CardanoBlock crypto)) where
parseJSON = error "FromJSON: GenTxId"
instance PraosCrypto crypto => FromJSON (GenTxId (CardanoBlock crypto)) where
parseJSON = decodeTxId

instance Crypto crypto => FromJSON (Point (CardanoBlock crypto)) where
parseJSON = decodePoint
Expand Down

0 comments on commit 655e569

Please sign in to comment.