cardano-addresses-4.0.0: Utils for constructing a command-line on top of cardano-addresses.
Copyright2020 Input Output (Hong Kong) Ltd. 2021-2022 Input Output Global Inc. (IOG) 2023-2025 Intersect
LicenseApache-2.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Address.Script

Description

 
Synopsis

Script

data Script (elem :: Type) Source #

A Script type represents multi signature script. The script embodies conditions that need to be satisfied to make it valid.

Since: 3.0.0

Instances

Instances details
Generic (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

Associated Types

type Rep (Script elem) :: Type -> Type #

Methods

from :: Script elem -> Rep (Script elem) x #

to :: Rep (Script elem) x -> Script elem #

Show elem => Show (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

Methods

showsPrec :: Int -> Script elem -> ShowS #

show :: Script elem -> String #

showList :: [Script elem] -> ShowS #

NFData elem => NFData (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

Methods

rnf :: Script elem -> () #

Eq elem => Eq (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

Methods

(==) :: Script elem -> Script elem -> Bool #

(/=) :: Script elem -> Script elem -> Bool #

FromJSON (Script KeyHash) Source # 
Instance details

Defined in Cardano.Address.Script

FromJSON (Script Cosigner) Source # 
Instance details

Defined in Cardano.Address.Script

ToJSON elem => ToJSON (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

Methods

toJSON :: Script elem -> Value #

toEncoding :: Script elem -> Encoding #

toJSONList :: [Script elem] -> Value #

toEncodingList :: [Script elem] -> Encoding #

omitField :: Script elem -> Bool #

type Rep (Script elem) Source # 
Instance details

Defined in Cardano.Address.Script

serializeScript :: Script KeyHash -> ByteString Source #

This function realizes what cardano-node's `Api.serialiseToCBOR script` realizes This is basically doing the symbolically following: toCBOR [0,multisigScript]

Since: 3.0.0

foldScript :: (a -> b -> b) -> b -> Script a -> b Source #

Script folding

Since: 3.2.0

Script template

data ScriptTemplate Source #

Represents the script template that show the structure of the script and determines the expected place of verification keys corresponding to given cosigners.

Since: 3.2.0

Instances

Instances details
Generic ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

Associated Types

type Rep ScriptTemplate :: Type -> Type #

Show ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

NFData ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

Methods

rnf :: ScriptTemplate -> () #

Eq ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

FromJSON ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

ToJSON ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ScriptTemplate Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ScriptTemplate = D1 ('MetaData "ScriptTemplate" "Cardano.Address.Script" "cardano-addresses-4.0.0-inplace" 'False) (C1 ('MetaCons "ScriptTemplate" 'PrefixI 'True) (S1 ('MetaSel ('Just "cosigners") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Cosigner XPub)) :*: S1 ('MetaSel ('Just "template") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Script Cosigner))))

newtype Cosigner Source #

Represents the cosigner of the script, ie., party that co-shares the script.

Since: 3.2.0

Constructors

Cosigner Word8 

Instances

Instances details
Generic Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

Associated Types

type Rep Cosigner :: Type -> Type #

Methods

from :: Cosigner -> Rep Cosigner x #

to :: Rep Cosigner x -> Cosigner #

Show Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

NFData Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

Methods

rnf :: Cosigner -> () #

Eq Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

Ord Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

Hashable Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

Methods

hashWithSalt :: Int -> Cosigner -> Int #

hash :: Cosigner -> Int #

FromJSON Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

ToJSON Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

FromJSON (Script Cosigner) Source # 
Instance details

Defined in Cardano.Address.Script

type Rep Cosigner Source # 
Instance details

Defined in Cardano.Address.Script

type Rep Cosigner = D1 ('MetaData "Cosigner" "Cardano.Address.Script" "cardano-addresses-4.0.0-inplace" 'True) (C1 ('MetaCons "Cosigner" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

Validation

data ValidationLevel Source #

Validation level. Required level does basic check that will make sure the script is accepted in ledger. Recommended level collects a number of checks that will warn about dangerous, unwise and redundant things present in the script.

Since: 3.2.0

Instances

Instances details
Generic ValidationLevel Source # 
Instance details

Defined in Cardano.Address.Script

Associated Types

type Rep ValidationLevel :: Type -> Type #

Show ValidationLevel Source # 
Instance details

Defined in Cardano.Address.Script

NFData ValidationLevel Source # 
Instance details

Defined in Cardano.Address.Script

Methods

rnf :: ValidationLevel -> () #

Eq ValidationLevel Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ValidationLevel Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ValidationLevel = D1 ('MetaData "ValidationLevel" "Cardano.Address.Script" "cardano-addresses-4.0.0-inplace" 'False) (C1 ('MetaCons "RequiredValidation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecommendedValidation" 'PrefixI 'False) (U1 :: Type -> Type))

validateScript :: ValidationLevel -> Script KeyHash -> Either ErrValidateScript () Source #

Validate a Script, semantically

Since: 3.0.0

prettyErrValidateScript :: ErrValidateScript -> String Source #

Pretty-print a script validation error.

Since: 3.0.0

prettyErrValidateScriptTemplate :: ErrValidateScriptTemplate -> String Source #

Pretty-print a script template validation error.

Since: 3.2.0

Hashing

newtype ScriptHash Source #

A ScriptHash type represents script hash. The hash is expected to have size of 28-byte.

Since: 3.0.0

Constructors

ScriptHash 

Instances

Instances details
Generic ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

Associated Types

type Rep ScriptHash :: Type -> Type #

Show ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

NFData ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

Methods

rnf :: ScriptHash -> () #

Eq ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

Ord ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ScriptHash Source # 
Instance details

Defined in Cardano.Address.Script

type Rep ScriptHash = D1 ('MetaData "ScriptHash" "Cardano.Address.Script" "cardano-addresses-4.0.0-inplace" 'True) (C1 ('MetaCons "ScriptHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unScriptHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

toScriptHash :: Script KeyHash -> ScriptHash Source #

Computes the hash of a given script, by first serializing it to CBOR.

Since: 3.0.0

scriptHashFromBytes :: ByteString -> Maybe ScriptHash Source #

Construct an ScriptHash from raw ByteString (28 bytes).

Since: 3.0.0

scriptHashToText :: ScriptHash -> KeyRole -> Maybe GovernanceType -> Text Source #

Encode a ScriptHash to bech32 Text or hex if key role is unknown. In the case of governance role, if one wants to include additional byte as specified in CIP-0129 unless the function is called with CIP0105.

One byte is prepended to script hash only in governance context. The rules how to contruct it are summarized below

  drep       0010....
  hot        0000....    key type
  cold       0001....

  scripthash ....0011    credential type

This is on top of X_script, where X={drep, cc_hot, cc_hot}, which lacks the additional byte. In scriptHashFromText we additionally support reading legacy X which also lacks the additional byte, and has the same payload as as the corresponding X_script.

Since: 4.0.0

scriptHashFromText :: Text -> Either ErrScriptHashFromText ScriptHash Source #

Construct a ScriptHash from Text. It should be

Bech32 encoded text with one of following hrp:

  • script
  • drep
  • cc_cold
  • cc_hot
  • drep_script
  • cc_cold_script
  • cc_hot_script

If if hex is encountered it is converted in rawly fashion

Since: 4.0.0

prettyErrScriptHashFromText :: ErrScriptHashFromText -> String Source #

Possible errors when deserializing a script hash from text.

Since: 4.0.0