Skip to content

Commit

Permalink
[WIP] Adding changes from #1073 on top of develop
Browse files Browse the repository at this point in the history
  • Loading branch information
rynoV committed Dec 2, 2022
1 parent c8c346d commit 3eb0540
Show file tree
Hide file tree
Showing 23 changed files with 263 additions and 309 deletions.
1 change: 1 addition & 0 deletions src/Contract/Transaction.purs
Expand Up @@ -279,6 +279,7 @@ import Effect.Aff (bracket)
import Effect.Aff.Class (liftAff)
import Effect.Class (liftEffect)
import Effect.Exception (throw)
-- TODO: Remove once toBytes is switched to Castable
import Untagged.Union (asOneOf)

-- | Signs a transaction with potential failure.
Expand Down
1 change: 1 addition & 0 deletions src/Internal/BalanceTx/ExUnitsAndMinFee.purs
Expand Up @@ -85,6 +85,7 @@ import Data.Traversable (for)
import Data.Tuple (fst, snd)
import Data.Tuple.Nested (type (/\), (/\))
import Effect.Class (liftEffect)
-- TODO: Remove once toBytes is switched to Castable
import Untagged.Union (asOneOf)

evalTxExecutionUnits
Expand Down
11 changes: 5 additions & 6 deletions src/Internal/Cardano/Types/Value.purs
Expand Up @@ -71,8 +71,8 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata)
import Ctl.Internal.Serialization.Hash
( ScriptHash
, scriptHashFromBytes
, scriptHashToBytes
)
import Ctl.Internal.Serialization.ToBytes (toBytes)
import Ctl.Internal.ToData (class ToData)
import Ctl.Internal.Types.ByteArray
( ByteArray
Expand Down Expand Up @@ -242,7 +242,7 @@ unsafeAdaSymbol = CurrencySymbol mempty
-- | constructor is not exported
mkCurrencySymbol :: ByteArray -> Maybe CurrencySymbol
mkCurrencySymbol byteArr =
scriptHashFromBytes (wrap byteArr) *> pure (CurrencySymbol byteArr)
scriptHashFromBytes byteArr *> pure (CurrencySymbol byteArr)

-- Do not export. Create an Ada `CurrencySymbol` from a `ByteArray`
mkUnsafeAdaSymbol :: ByteArray -> Maybe CurrencySymbol
Expand Down Expand Up @@ -778,10 +778,10 @@ filterNonAda (Value _ nonAda) = Value mempty nonAda
-- already know is a valid CurrencySymbol
currencyScriptHash :: CurrencySymbol -> ScriptHash
currencyScriptHash (CurrencySymbol byteArray) =
unsafePartial fromJust $ scriptHashFromBytes (wrap byteArray)
unsafePartial fromJust $ scriptHashFromBytes byteArray

scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol
scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< scriptHashToBytes
scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes

-- | The minting policy hash of a currency symbol
currencyMPSHash :: CurrencySymbol -> MintingPolicyHash
Expand All @@ -792,8 +792,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash
-- Plutus doesn't use Maybe here.
-- | The currency symbol of a monetary policy hash
mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol
mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol <<< unwrap $
scriptHashToBytes h
mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h

-- Like `mapEither` that works with 'These'.
mapThese
Expand Down
24 changes: 23 additions & 1 deletion src/Internal/Deserialization/Error.purs
@@ -1,18 +1,21 @@
-- | Error-centered types and functions used by Deserialization modules.
module Ctl.Internal.Deserialization.Error
( Err
, FromBytesError
, FromCslRepError
, _fromCslRepError
, addErrTrace
, cslErr
, fromBytesErrorHelper
, fromBytesError
, fromCslRepError
, toError
) where

import Prelude

import Ctl.Internal.Deserialization.FromBytes (FromBytesError, _fromBytesError)
import Ctl.Internal.Error (E, NotImplementedError, _notImplementedError, noteE)
import Ctl.Internal.FfiHelpers (ErrorFfiHelper, errorHelper)
import Data.Either (Either(Left))
import Data.Maybe (Maybe)
import Data.Variant (Variant, default, inj, match, onMatch)
Expand Down Expand Up @@ -66,3 +69,22 @@ toError = error <<< match
, fromBytesError: \err -> "FromBytesError: " <> err
, notImplementedError: \err -> "NotImplementedError: " <> err
}

-- | FromBytesError row alias
type FromBytesError r = (fromBytesError :: String | r)

-- | Needed to craate a variant type
_fromBytesError = Proxy :: Proxy "fromBytesError"

-- | An error to use
fromBytesError
:: forall (r :: Row Type) (a :: Type)
. String
-> E (FromBytesError + r) a
fromBytesError = Left <<< inj _fromBytesError

-- | An internal helper to shorten code
fromBytesErrorHelper
:: forall (r :: Row Type)
. ErrorFfiHelper (FromBytesError + r)
fromBytesErrorHelper = errorHelper (inj _fromBytesError)
17 changes: 1 addition & 16 deletions src/Internal/Deserialization/FromBytes.js
Expand Up @@ -7,25 +7,10 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) {
lib = require("@emurgo/cardano-serialization-lib-nodejs");
}

const fromBytes = name => helper => bytes => {
exports._fromBytes = name => helper => bytes => {
try {
return helper.valid(lib[name].from_bytes(bytes));
} catch (e) {
return helper.error(name + ".from_bytes() raised " + e);
}
};

exports._fromBytesDataHash = fromBytes("DataHash");
exports._fromBytesTransaction = fromBytes("Transaction");
exports._fromBytesTransactionHash = fromBytes("TransactionHash");
exports._fromBytesPlutusData = fromBytes("PlutusData");
exports._fromBytesTransactionUnspentOutput = fromBytes(
"TransactionUnspentOutput"
);
exports._fromBytesTransactionWitnessSet = fromBytes("TransactionWitnessSet");
exports._fromBytesNativeScript = fromBytes("NativeScript");
exports._fromBytesMint = fromBytes("Mint");
exports._fromBytesVRFKeyHash = fromBytes("VRFKeyHash");
exports._fromBytesValue = fromBytes("Value");
exports._fromBytesPublicKey = fromBytes("PublicKey");
exports._fromBytesEd25519Signature = fromBytes("Ed25519Signature");
148 changes: 53 additions & 95 deletions src/Internal/Deserialization/FromBytes.purs
@@ -1,155 +1,113 @@
module Ctl.Internal.Deserialization.FromBytes
( class FromBytes
, FromBytesError
, _fromBytesError
, fromBytesError
, fromBytes'
, fromBytes
, fromBytesEffect
) where

import Prelude

import Ctl.Internal.Deserialization.Error (FromBytesError, fromBytesErrorHelper)
import Ctl.Internal.Error (E)
import Ctl.Internal.FfiHelpers (ErrorFfiHelper, errorHelper)
import Ctl.Internal.FfiHelpers (ErrorFfiHelper)
import Ctl.Internal.Serialization.Hash (VRFKeyHash)
import Ctl.Internal.Serialization.Types
( DataHash
( AuxiliaryDataHash
, DataHash
, Ed25519Signature
, GenesisDelegateHash
, GenesisHash
, Mint
, NativeScript
, PlutusData
, PoolMetadataHash
, PublicKey
, ScriptDataHash
, Transaction
, TransactionHash
, TransactionUnspentOutput
, TransactionWitnessSet
, VRFKeyHash
, Value
)
import Ctl.Internal.Types.ByteArray (ByteArray)
import Data.Either (Either(Left), hush)
import Ctl.Internal.Types.CborBytes (CborBytes)
import Data.Either (hush)
import Data.Maybe (Maybe(Just, Nothing))
import Data.Variant (inj)
import Data.Newtype (unwrap)
import Effect (Effect)
import Effect.Exception (throw)
import Type.Prelude (Proxy(Proxy))
import Type.Row (type (+))

-- | Calls `from_bytes` method for the appropriate type
class FromBytes a where
fromBytes' :: forall (r :: Row Type). ByteArray -> E (FromBytesError + r) a

instance FromBytes AuxiliaryDataHash where
fromBytes' = _fromBytes "AuxiliaryDataHash" fromBytesErrorHelper

instance FromBytes DataHash where
fromBytes' = _fromBytesDataHash eh
fromBytes' = _fromBytes "DataHash" fromBytesErrorHelper

instance FromBytes Transaction where
fromBytes' = _fromBytesTransaction eh
instance FromBytes GenesisDelegateHash where
fromBytes' = _fromBytes "GenesisDelegateHash" fromBytesErrorHelper

instance FromBytes TransactionHash where
fromBytes' = _fromBytesTransactionHash eh
instance FromBytes GenesisHash where
fromBytes' = _fromBytes "GenesisHash" fromBytesErrorHelper

instance FromBytes Mint where
fromBytes' = _fromBytes "Mint" fromBytesErrorHelper

instance FromBytes NativeScript where
fromBytes' = _fromBytes "NativeScript" fromBytesErrorHelper

instance FromBytes PlutusData where
fromBytes' = _fromBytesPlutusData eh
fromBytes' = _fromBytes "PlutusData" fromBytesErrorHelper

instance FromBytes TransactionUnspentOutput where
fromBytes' = _fromBytesTransactionUnspentOutput eh
instance FromBytes PoolMetadataHash where
fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper

instance FromBytes TransactionWitnessSet where
fromBytes' = _fromBytesTransactionWitnessSet eh
instance FromBytes ScriptDataHash where
fromBytes' = _fromBytes "ScriptDataHash" fromBytesErrorHelper

instance FromBytes NativeScript where
fromBytes' = _fromBytesNativeScript eh
instance FromBytes Transaction where
fromBytes' = _fromBytes "Transaction" fromBytesErrorHelper

instance FromBytes Mint where
fromBytes' = _fromBytesMint eh
instance FromBytes TransactionHash where
fromBytes' = _fromBytes "TransactionHash" fromBytesErrorHelper

instance FromBytes VRFKeyHash where
fromBytes' = _fromBytesVRFKeyHash eh
instance FromBytes TransactionUnspentOutput where
fromBytes' = _fromBytes "TransactionUnspentOutput" fromBytesErrorHelper

instance FromBytes TransactionWitnessSet where
fromBytes' = _fromBytes "TransactionWitnessSet" fromBytesErrorHelper

instance FromBytes Value where
fromBytes' = _fromBytesValue eh
fromBytes' = _fromBytes "Value" fromBytesErrorHelper

instance FromBytes PublicKey where
fromBytes' = _fromBytesPublicKey eh
fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper

instance FromBytes Ed25519Signature where
fromBytes' = _fromBytesEd25519Signature eh
fromBytes' = _fromBytes "Ed25519Signature" fromBytesErrorHelper

instance FromBytes VRFKeyHash where
fromBytes' = _fromBytes "VRFKeyHash" fromBytesErrorHelper

-- for backward compatibility until `Maybe` is abandoned. Then to be renamed.
fromBytes :: forall (a :: Type). FromBytes a => ByteArray -> Maybe a
fromBytes = fromBytes' >>> hush
fromBytes :: forall (a :: Type). FromBytes a => CborBytes -> Maybe a
fromBytes = unwrap >>> fromBytes' >>> hush

fromBytesEffect :: forall (a :: Type). FromBytes a => ByteArray -> Effect a
fromBytesEffect :: forall (a :: Type). FromBytes a => CborBytes -> Effect a
fromBytesEffect bytes =
case fromBytes bytes of
Nothing -> throw "from_bytes() call failed"
Just a -> pure a

---- Error types

-- | FromBytesError row alias
type FromBytesError r = (fromBytesError :: String | r)

-- | Needed to craate a variant type
_fromBytesError = Proxy :: Proxy "fromBytesError"
---- Foreign imports

-- | An error to use
fromBytesError
foreign import _fromBytes
:: forall (r :: Row Type) (a :: Type)
. String
-> E (FromBytesError + r) a
fromBytesError = Left <<< inj _fromBytesError

-- | A local helper to shorten code
eh :: forall (r :: Row Type). ErrorFfiHelper (FromBytesError + r)
eh = errorHelper (inj _fromBytesError)

---- Foreign imports

foreign import _fromBytesDataHash
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r DataHash

foreign import _fromBytesTransactionHash
:: forall (r :: Row Type)
. ErrorFfiHelper r
-> ByteArray
-> E r TransactionHash

foreign import _fromBytesPlutusData
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r PlutusData

foreign import _fromBytesTransaction
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Transaction

foreign import _fromBytesTransactionUnspentOutput
:: forall (r :: Row Type)
. ErrorFfiHelper r
-> ByteArray
-> E r TransactionUnspentOutput

foreign import _fromBytesTransactionWitnessSet
:: forall (r :: Row Type)
. ErrorFfiHelper r
-> ByteArray
-> E r TransactionWitnessSet

foreign import _fromBytesNativeScript
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r NativeScript

foreign import _fromBytesMint
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Mint

foreign import _fromBytesVRFKeyHash
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r VRFKeyHash

foreign import _fromBytesValue
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Value

foreign import _fromBytesPublicKey
:: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r PublicKey

foreign import _fromBytesEd25519Signature
:: forall (r :: Row Type)
. ErrorFfiHelper r
-> ErrorFfiHelper r
-> ByteArray
-> E r Ed25519Signature
-> E r a
3 changes: 1 addition & 2 deletions src/Internal/QueryM.purs
Expand Up @@ -278,7 +278,6 @@ import Effect.Exception (Error, error, throw, try)
import Effect.Ref (Ref)
import Effect.Ref as Ref
import Foreign.Object as Object
import Untagged.Union (asOneOf)

-- This module defines an Aff interface for Ogmios Websocket Queries
-- Since WebSockets do not define a mechanism for linking request/response
Expand Down Expand Up @@ -844,8 +843,8 @@ applyArgs script args =
map
( encodeAeson
<<< byteArrayToHex
<<< unwrap
<<< Serialization.toBytes
<<< asOneOf
)
<<< Serialization.convertPlutusData

Expand Down
3 changes: 1 addition & 2 deletions src/Internal/QueryM/Ogmios.purs
Expand Up @@ -164,7 +164,6 @@ import Ctl.Internal.Types.Natural (Natural)
import Ctl.Internal.Types.Natural (fromString) as Natural
import Ctl.Internal.Types.Rational (Rational, (%))
import Ctl.Internal.Types.Rational as Rational
import Ctl.Internal.Types.RawBytes (hexToRawBytes)
import Ctl.Internal.Types.RedeemerTag (RedeemerTag)
import Ctl.Internal.Types.RedeemerTag (fromString) as RedeemerTag
import Ctl.Internal.Types.RewardAddress (RewardAddress)
Expand Down Expand Up @@ -1573,7 +1572,7 @@ parseScript outer =
pubKeyHashHex = unsafePartial fromJust $ toString aeson

ScriptPubkey <$> note pubKeyHashTypeMismatch
(ed25519KeyHashFromBytes =<< hexToRawBytes pubKeyHashHex)
(ed25519KeyHashFromBytes =<< hexToByteArray pubKeyHashHex)

| otherwise = aeson # aesonObject \obj -> do
let
Expand Down

0 comments on commit 3eb0540

Please sign in to comment.