Skip to content

Commit

Permalink
JSON instance for FullTx
Browse files Browse the repository at this point in the history
  • Loading branch information
j-mueller committed Dec 13, 2024
1 parent 09fa66b commit fe60f8b
Showing 1 changed file with 28 additions and 12 deletions.
40 changes: 28 additions & 12 deletions src/base/lib/Convex/UtxoMod.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
{-| Changing hashes
-}
Expand All @@ -12,17 +14,19 @@ module Convex.UtxoMod(
FullTx(..)
) where

import Cardano.Api (Hash, Script, ScriptHash,
ScriptInAnyLang (..))
import qualified Cardano.Api as C
import Cardano.Binary (DecoderError)
import Control.Monad (guard)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Functor (($>))
import Data.Map (Map)
import Data.Proxy (Proxy (..))
import GHC.Generics (Generic)
import Cardano.Api (Hash, Script, ScriptHash,
ScriptInAnyLang (..))
import qualified Cardano.Api as C
import Cardano.Binary (DecoderError)
import Control.Monad (guard)
import Data.Aeson (FromJSON (..), ToJSON (..), withObject, (.:))
import Data.Aeson.Types (object, (.=))
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Functor (($>))
import Data.Map (Map)
import Data.Proxy (Proxy (..))
import GHC.Generics (Generic)

{-| Replace all occurrences of a hash in the serialised script
with a new hash. Throws an 'error' if it fails
Expand Down Expand Up @@ -100,4 +104,16 @@ data FullTx =
, ftxInputs :: Map C.TxIn (C.TxOut C.CtxUTxO C.ConwayEra)
}
deriving stock (Eq, Show, Generic)
-- deriving anyclass (ToJSON, FromJSON)

instance ToJSON FullTx where
toJSON FullTx{ftxTransaction, ftxInputs} =
object
[ "transaction" .= C.serialiseToTextEnvelope Nothing ftxTransaction
, "inputs" .= ftxInputs
]

instance FromJSON FullTx where
parseJSON = withObject "FullTx" $ \obj ->
FullTx
<$> (obj .: "transaction" >>= either (fail . show) pure . C.deserialiseFromTextEnvelope (C.proxyToAsType Proxy))
<*> obj .: "inputs"

0 comments on commit fe60f8b

Please sign in to comment.