plutarch-ledger-api-3.2.1
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plutarch.LedgerApi.AssocMap

Description

This module is designed to be imported qualified, as many of its identifiers clash with the Plutarch prelude.

Synopsis

Types

newtype PMap (keysort :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S) Source #

Since: 2.0.0

Constructors

PMap (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))) 

Instances

Instances details
(POrd k, PIsData k, PTryFrom PData (PAsData k), PTryFrom PData (PAsData v)) => PTryFrom PData (PAsData (PMap 'Sorted k v)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PMap 'Sorted k v)), Reduce (PTryFromExcess PData (PAsData (PMap 'Sorted k v)) s)) -> Term s r) -> Term s r

(PTryFrom PData (PAsData k), PTryFrom PData (PAsData v)) => PTryFrom PData (PAsData (PMap 'Unsorted k v)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PMap 'Unsorted k v)), Reduce (PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) s)) -> Term s r) -> Term s r

PIsData (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PMap keysort k v)) -> Term s (PMap keysort k v)

pdataImpl :: forall (s :: S). Term s (PMap keysort k v) -> Term s PData

PEq (PMap 'Sorted k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

(#==) :: forall (s :: S). Term s (PMap 'Sorted k v) -> Term s (PMap 'Sorted k v) -> Term s PBool

(ToData (AsHaskell k), ToData (AsHaskell v), FromData (AsHaskell k), FromData (AsHaskell v)) => PLiftable (PMap 'Unsorted k v) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type AsHaskell (PMap 'Unsorted k v)

type PlutusRepr (PMap 'Unsorted k v)

Methods

toPlutarchRepr :: AsHaskell (PMap 'Unsorted k v) -> PlutusRepr (PMap 'Unsorted k v)

toPlutarch :: forall (s :: S). AsHaskell (PMap 'Unsorted k v) -> PLifted s (PMap 'Unsorted k v)

fromPlutarchRepr :: PlutusRepr (PMap 'Unsorted k v) -> Maybe (AsHaskell (PMap 'Unsorted k v))

fromPlutarch :: (forall (s :: S). PLifted s (PMap 'Unsorted k v)) -> Either LiftError (AsHaskell (PMap 'Unsorted k v))

DerivePlutusType (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type DPTStrat (PMap keysort k v)

PlutusType (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PInner (PMap keysort k v) :: PType

type PCovariant' (PMap keysort k v)

type PContravariant' (PMap keysort k v)

type PVariant' (PMap keysort k v)

Methods

pcon' :: forall (s :: S). PMap keysort k v s -> Term s (PInner (PMap keysort k v))

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMap keysort k v)) -> (PMap keysort k v s -> Term s b) -> Term s b

(PIsData k, PIsData v, PShow k, PShow v) => PShow (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMap keysort k v) -> Term s PString

Generic (PMap keysort k v s) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type Rep (PMap keysort k v s) :: Type -> Type Source #

Methods

from :: PMap keysort k v s -> Rep (PMap keysort k v s) x Source #

to :: Rep (PMap keysort k v s) x -> PMap keysort k v s Source #

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) = Mret (PMap 'Sorted k v)
type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) = Mret (PMap 'Unsorted k v)
type AsHaskell (PMap 'Unsorted k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type AsHaskell (PMap 'Unsorted k v) = Map (AsHaskell k) (AsHaskell v)
type PlutusRepr (PMap 'Unsorted k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PlutusRepr (PMap 'Unsorted k v) = [(Data, Data)]
type DPTStrat (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type DPTStrat (PMap keysort k v) = PlutusTypeNewtype
type PContravariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PContravariant' (PMap keysort k v) = All2 PContravariant'' (PCode (PMap keysort k v))
type PCovariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PCovariant' (PMap keysort k v) = All2 PCovariant'' (PCode (PMap keysort k v))
type PInner (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PInner (PMap keysort k v) = DerivedPInner (DPTStrat (PMap keysort k v)) (PMap keysort k v)
type PVariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PVariant' (PMap keysort k v) = All2 PVariant'' (PCode (PMap keysort k v))
type Rep (PMap keysort k v s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

type Rep (PMap keysort k v s) = D1 ('MetaData "PMap" "Plutarch.LedgerApi.AssocMap" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))))))

data KeyGuarantees Source #

Since: 2.0.0

Constructors

Sorted 
Unsorted 

Functions

Creation

pempty :: Term s (PMap 'Sorted k v) Source #

Construct an empty PMap.

Since: 2.0.0

psingleton :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PIsData v) => Term s (k :--> (v :--> PMap 'Sorted k v)) Source #

Construct a singleton PMap with the given key and value.

Since: 2.1.1

psingletonData :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). Term s (PAsData k :--> (PAsData v :--> PMap 'Sorted k v)) Source #

Construct a singleton PMap with the given data-encoded key and value.

Since: 2.1.1

punsortedMapFromFoldable :: forall (k :: S -> Type) (v :: S -> Type) (f :: Type -> Type) (s :: S). (Foldable f, PIsData k, PIsData v) => f (Term s k, Term s v) -> Term s (PMap 'Unsorted k v) Source #

Since: 2.1.1

psortedMapFromFoldable :: forall (k :: S -> Type) (v :: S -> Type) (f :: Type -> Type) (s :: S). (Foldable f, POrd k, PIsData k, PIsData v) => f (Term s k, Term s v) -> Term s (PMap 'Sorted k v) Source #

Since: 2.1.1

Transformation

passertSorted :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (s :: S). (POrd k, PIsData k) => Term s (PMap any k v :--> PMap 'Sorted k v) Source #

Given a PMap of uncertain order, yield a PMap that is known to be sorted.

Since: 2.0.0

pforgetSorted :: forall (g :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S). Term s (PMap 'Sorted k v) -> Term s (PMap g k v) Source #

Forget the knowledge that keys were sorted.

Since: 2.1.1

pmap :: forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). (PIsData a, PIsData b) => Term s ((a :--> b) :--> (PMap g k a :--> PMap g k b)) Source #

Applies a function to every value in the map, much like map.

Since: 2.0.0

pmapData :: forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). Term s ((PAsData a :--> PAsData b) :--> (PMap g k a :--> PMap g k b)) Source #

As pmap, but over Data representations.

Since: 2.0.0

pmapWithKey :: forall (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (keysort :: KeyGuarantees) (s :: S). (PIsData k, PIsData a, PIsData b) => Term s ((k :--> (a :--> b)) :--> (PMap keysort k a :--> PMap 'Unsorted k b)) Source #

As pmap, but gives key access as well.

Since: 2.1.1

pmapMaybe :: forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). (PIsData a, PIsData b) => Term s ((a :--> PMaybe b) :--> (PMap g k a :--> PMap g k b)) Source #

Maps and filters the map, much like mapMaybe.

Since: 2.0.0

pmapMaybeData :: forall (g :: KeyGuarantees) (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). Term s ((PAsData a :--> PMaybe (PAsData b)) :--> (PMap g k a :--> PMap g k b)) Source #

As pmapMaybe, but over Data representation.

Since: 2.0.0

Relational lift

pcheckBinRel :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k, PIsData v) => Term s ((v :--> (v :--> PBool)) :--> (v :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PBool)))) Source #

Given a comparison function and a "zero" value, check whether a binary relation holds over 2 sorted PMaps.

Important note

This is primarily intended to be used with PValue. We assume that the comparison behaves like a comparison would (thus, being at least a partial order, or possibly a total order or equivalence), and that the starting value does not break it. Use with extreme care.

Since: 2.0.0

Comparison

pkeysEqual :: forall (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). (PEq k, PIsData k) => Term s (PMap 'Sorted k a :--> (PMap 'Sorted k b :--> PBool)) Source #

Gives PTrue if both argument PMaps contain mappings for exactly the same set of keys. Requires a number of equality comparisons between keys proportional to the length of the shorter argument.

Since: 2.1.1

pkeysEqualUnsorted :: forall (k :: S -> Type) (a :: S -> Type) (b :: S -> Type) (s :: S). (PIsData k, PIsData a, PIsData b) => Term s (PMap 'Unsorted k a :--> (PMap 'Unsorted k b :--> PBool)) Source #

As pkeysEqual, but requires only PEq constraints for the keys, and works for Unsorted PMaps. This requires a number of equality comparisons between keys proportional to the product of the lengths of both arguments: that is, this function is quadratic.

Since: 2.1.1

Fold

pall :: forall (any :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S). PIsData v => Term s ((v :--> PBool) :--> (PMap any k v :--> PBool)) Source #

Verifies all values in the map satisfy the given predicate.

Since: 2.0.0

pany :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (s :: S). PIsData v => Term s ((v :--> PBool) :--> (PMap any k v :--> PBool)) Source #

Tests if anu value in the map satisfies the given predicate.

Since: 2.1.1

pfoldMapWithKey :: forall (m :: S -> Type) (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PIsData v, forall (s' :: S). Monoid (Term s' m)) => Term s ((k :--> (v :--> m)) :--> (PMap 'Sorted k v :--> m)) Source #

Project all key-value pairs into a Monoid, then combine. Keys and values will be presented in key order.

Since: 2.1.1

pfoldlWithKey :: forall (a :: S -> Type) (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PIsData v) => Term s ((a :--> (k :--> (v :--> a))) :--> (a :--> (PMap 'Sorted k v :--> a))) Source #

Left-associative fold of a PMap with keys. Keys and values will be presented in key order.

Since: 2.1.1

Combination

punionResolvingCollisionsWith :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k, PIsData v) => Commutativity -> Term s ((v :--> (v :--> v)) :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Build the union of two PMaps, merging values that share the same key using the given function.

Since: 2.0.0

punionResolvingCollisionsWithData :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k) => Commutativity -> Term s ((PAsData v :--> (PAsData v :--> PAsData v)) :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Build the union of two PMaps, merging values that share the same key using the given function.

Since: 2.1.1

pleftBiasedUnion :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k, PIsData v) => Term s (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v)) Source #

Build the union of two PMaps. Take the value from the left argument for colliding keys.

Prefer this over 'punionResolvingCollisionsWith NonCommutative # plam const'. It performs better.

Since: 2.1.1

pdifference :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, POrd k, PIsData v) => Term s (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v)) Source #

Difference of two maps. Return elements of the first map not existing in the second map.

Since: 2.1.1

pzipWithDefaults :: forall (s :: S) (k :: S -> Type) (v :: S -> Type). (POrd k, PIsData k, PIsData v) => (forall (s' :: S). Term s' v) -> (forall (s' :: S). Term s' v) -> Term s ((v :--> (v :--> v)) :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Zip two PMaps, using the given potentially non-commutative value merge function for key collisions, and different values for the sides.

Since: 2.1.1

pintersectionWith :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k, PIsData v) => Commutativity -> Term s ((v :--> (v :--> v)) :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Build the intersection of two PMaps, merging values that share the same key using the given function.

Since: 2.1.1

pintersectionWithData :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k) => Commutativity -> Term s ((PAsData v :--> (PAsData v :--> PAsData v)) :--> (PMap 'Sorted k v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Build the intersection of two PMaps, merging data-encoded values that share the same key using the given function.

Since: 2.1.1

Query

pnull :: forall (any :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S). Term s (PMap any k v :--> PBool) Source #

Tests whether the map is empty.

Since: 2.0.0

plookup :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (s :: S). (PIsData k, PIsData v) => Term s (k :--> (PMap any k v :--> PMaybe v)) Source #

Look up the given key in a PMap.

Since: 2.1.1

plookupData :: Term s (PAsData k :--> (PMap any k v :--> PMaybe (PAsData v))) Source #

as plookup, except over Data representation.

Since: 2.1.1

plookupDataWith :: Term s ((PBuiltinPair (PAsData k) (PAsData v) :--> PMaybe x) :--> (PAsData k :--> (PMap any k v :--> PMaybe x))) Source #

Look up the given key data in a PMap, applying the given function to the found key-value pair.

Since: 2.1.1

pfindWithDefault :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (s :: S). (PIsData k, PIsData v) => Term s (v :--> (k :--> (PMap any k v :--> v))) Source #

Look up the given key in a PMap, returning the default value if the key is absent.

Since: 2.1.1

pfoldAt :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (r :: S -> Type) (s :: S). PIsData k => Term s (k :--> (r :--> ((PAsData v :--> r) :--> (PMap any k v :--> r)))) Source #

Look up the given key in a PMap; return the default if the key is absent or apply the argument function to the value data if present.

Since: 2.1.1

pfoldAtData :: forall (k :: S -> Type) (v :: S -> Type) (any :: KeyGuarantees) (r :: S -> Type) (s :: S). Term s (PAsData k :--> (r :--> ((PAsData v :--> r) :--> (PMap any k v :--> r)))) Source #

Look up the given key data in a PMap; return the default if the key is absent or apply the argument function to the value data if present.

Since: 2.1.1

ptryLookup :: forall (k :: S -> Type) (v :: S -> Type) (keys :: KeyGuarantees) (s :: S). (PIsData k, PIsData v) => Term s (k :--> (PMap keys k v :--> v)) Source #

As plookup, but errors when the key is missing.

Since: 2.1.1

Modification

pinsert :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k, PIsData v) => Term s (k :--> (v :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Insert a new key/value pair into the map, overriding the previous if any.

Since: 2.1.1

pdelete :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (POrd k, PIsData k) => Term s (k :--> (PMap 'Sorted k v :--> PMap 'Sorted k v)) Source #

Delete a key from the map.

Since: 2.1.1

pupdate :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PIsData v, POrd k) => Term s ((v :--> PMaybe v) :--> (k :--> (PMap 'Sorted k v :--> PMap 'Sorted k v))) Source #

Given an 'updater' and a key, if the key exists in the PMap, apply the 'updater' to it, otherwise do nothing. If the 'updater' produces PNothing, the value is deleted; otherwise, it is modified to the result.

Performance will be equivalent to a lookup followed by an insert (or delete), as well as the cost of calling the 'updater'.

Since: 2.1.1

padjust :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PEq k, PIsData v) => Term s ((v :--> v) :--> (k :--> (PMap 'Unsorted k v :--> PMap 'Unsorted k v))) Source #

If a value exists at the specified key, apply the function argument to it; otherwise, do nothing.

Since: 2.1.1

Key-value pair manipulation

pkvPairKey :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). PIsData k => Term s (PBuiltinPair (PAsData k) (PAsData v) :--> k) Source #

Get the key of a key-value pair.

Since: 2.1.1

pkvPairValue :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). PIsData v => Term s (PBuiltinPair (PAsData k) (PAsData v) :--> v) Source #

Get the value of a key-value pair.

Since: 2.1.1

pkvPairLt :: forall (k :: S -> Type) (v :: S -> Type) (s :: S). (PIsData k, PPartialOrd k) => Term s (PBuiltinPair (PAsData k) (PAsData v) :--> (PBuiltinPair (PAsData k) (PAsData v) :--> PBool)) Source #

Compare two key-value pairs by their keys. Gives PTrue if the key of the first argument pair is less than the key of the second argument pair.

Since: 2.1.1

Conversion

pkeys :: forall (ell :: (S -> Type) -> S -> Type) (k :: S -> Type) (v :: S -> Type) (keys :: KeyGuarantees) (s :: S). (PListLike ell, PElemConstraint ell (PAsData k)) => Term s (PMap keys k v :--> ell (PAsData k)) Source #

Get a list-like structure full of the keys of the argument PMap. If the PMap is Sorted, the keys will maintain that order, and will be unique; otherwise, the order is unspecified, and duplicates may exist.

Note

You will need to specify what manner of list-like structure you want; we have arranged the type signature to make specifying this easy with TypeApplications.

Since: 2.1.1