Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- class PDataFields (a :: S -> Type) where
- type PFields a :: [PLabeledType]
- ptoFields :: Term s a -> Term s (PDataRecord (PFields a))
- pletFields :: forall fs a s b ps bs. (PDataFields a, ps ~ PFields a, bs ~ Bindings ps fs, BindFields ps bs) => Term s a -> (HRecOf a fs s -> Term s b) -> Term s b
- pfield :: forall name b p s a as n. (PDataFields p, as ~ PFields p, n ~ PLabelIndex name as, KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) => Term s (p :--> b)
- class BindFields (ps :: [PLabeledType]) (bs :: [ToBind]) where
- bindFields :: Proxy bs -> Term s (PDataRecord ps) -> TermCont s (HRec (BoundTerms ps bs s))
- type family Bindings (ps :: [PLabeledType]) (fs :: [Symbol]) :: [ToBind] where ...
- type family BoundTerms ps bs s where ...
- type family Drop (n :: Nat) (as :: [k]) :: [k] where ...
- type HRecOf t fs s = HRec (BoundTerms (PFields t) (Bindings (PFields t) fs) s)
- type family PMemberFields t fs s as where ...
- type family PMemberField t name s as where ...
- data HRec as where
- newtype Labeled sym a = Labeled {
- unLabeled :: a
- hrecField :: forall name c as a b s. (ElemOf name a as, Term s (PAsData b) ~ a, PFromDataable b c) => HRec as -> Term s c
PDataField class & deriving utils
class PDataFields (a :: S -> Type) where Source #
Class allowing letFields
to work for a PType, usually via
PIsDataRepr
, but is derived for some other types for convenience.
Nothing
type PFields a :: [PLabeledType] Source #
Fields in HRec bound by letFields
Instances
(PIsData a, PDataFields a) => PDataFields (PAsData a) Source # | |
PDataFields (PDataRecord as) Source # | |
Defined in Plutarch.DataRepr.Internal.Field type PFields (PDataRecord as) :: [PLabeledType] Source # ptoFields :: forall (s :: S). Term s (PDataRecord as) -> Term s (PDataRecord (PFields (PDataRecord as))) Source # | |
PDataFields (PDataSum '[as]) Source # | |
pletFields :: forall fs a s b ps bs. (PDataFields a, ps ~ PFields a, bs ~ Bindings ps fs, BindFields ps bs) => Term s a -> (HRecOf a fs s -> Term s b) -> Term s b Source #
Bind a HRec of named fields containing all the specified fields.
pfield :: forall name b p s a as n. (PDataFields p, as ~ PFields p, n ~ PLabelIndex name as, KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) => Term s (p :--> b) Source #
Get a single field from a Term.
- NB*: If you access more than one field from
the same value you should use
pletFields
instead, which will generate the bindings more efficiently.
BindFields class mechanism
class BindFields (ps :: [PLabeledType]) (bs :: [ToBind]) where Source #
bindFields :: Proxy bs -> Term s (PDataRecord ps) -> TermCont s (HRec (BoundTerms ps bs s)) Source #
Bind all the fields in a PDataList
term to a corresponding
HList of Terms.
A continuation is returned to enable sharing of the generated bound-variables.
type family Bindings (ps :: [PLabeledType]) (fs :: [Symbol]) :: [ToBind] where ... Source #
Map BindField
over [PLabeledType]
, with Skips
removed at tail
type family BoundTerms ps bs s where ... Source #
BoundTerms '[] _ _ = '[] | |
BoundTerms _ '[] _ = '[] | |
BoundTerms (_ ': ps) ('Skip ': bs) s = BoundTerms ps bs s | |
BoundTerms ((name ':= p) ': ps) ('Bind ': bs) s = '(name, Term s (PAsData p)) ': BoundTerms ps bs s |
type HRecOf t fs s = HRec (BoundTerms (PFields t) (Bindings (PFields t) fs) s) Source #
The HRec
yielded by 'pletFields @fs t'.
type family PMemberFields t fs s as where ... Source #
Constrain an HRec
to contain the specified fields from the given Plutarch type.
Example ===
import qualified GHC.Generics as GHC
import Generics.SOP
import Plutarch.Prelude
import Plutarch.DataRepr
newtype PFooType s = PFooType (Term s (PDataRecord '["frst" ':= PInteger, "scnd" ':= PBool, "thrd" ':= PString]))
deriving stock (GHC.Generic)
deriving anyclass (Generic)
deriving anyclass (PIsDataRepr)
deriving
(PlutusType, PIsData, PDataFields, PEq)
via PIsDataReprInstances PFooType
foo :: PMemberFields PFooType '["scnd", "frst"] s as => HRec as -> Term s PInteger
foo h = pif (getField "scnd" h) (getField
"frst" h) 0
PMemberFields _ '[] _ _ = () | |
PMemberFields t (name ': rest) s as = (PMemberField t name s as, PMemberFields t rest s as) |
type family PMemberField t name s as where ... Source #
Single field version of PMemberFields
.
PMemberField t name s as = (IndexLabel name as ~ Term s (PAsData (PLookupLabel name (PFields t))), ElemOf name (Term s (PAsData (PLookupLabel name (PFields t)))) as) |
Re-exports
hrecField :: forall name c as a b s. (ElemOf name a as, Term s (PAsData b) ~ a, PFromDataable b c) => HRec as -> Term s c Source #
Deprecated: please use getField from GHC.Records
Index a HRec
with a field in a provided list of data fields.
Implicitly unwraps `PAsData a` to a
when necessary.
>>>
xs = HRec @["x", "y", "z"] (HCons 1 (HCons 2 (HCons 3 HNil)))
>>>
hrecField @"y" @["x", "y", "z"] xs
>>>
2