Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Instructions working on product types derived from Haskell ones.
Synopsis
- type InstrGetFieldC dt name = (GenericIsoValue dt, GInstrGet name (GRep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt)))
- type InstrSetFieldC dt name = (GenericIsoValue dt, GInstrSetField name (GRep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt)))
- type InstrConstructC dt = (GenericIsoValue dt, GInstrConstruct (GRep dt) '[])
- instrToField :: forall dt name st. InstrGetFieldC dt name => Label name -> Instr (ToT dt ': st) (ToT (GetFieldType dt name) ': st)
- instrGetField :: forall dt name st. (InstrGetFieldC dt name, DupableScope (ToT (GetFieldType dt name))) => Label name -> Instr (ToT dt ': st) (ToT (GetFieldType dt name) ': (ToT dt ': st))
- instrGetFieldOpen :: forall dt name res st. InstrGetFieldC dt name => Instr '[ToT (GetFieldType dt name)] '[res, ToT (GetFieldType dt name)] -> Instr '[ToT (GetFieldType dt name)] '[res] -> Label name -> Instr (ToT dt ': st) (res ': (ToT dt ': st))
- instrSetField :: forall dt name st. InstrSetFieldC dt name => Label name -> Instr (ToT (GetFieldType dt name) ': (ToT dt ': st)) (ToT dt ': st)
- instrSetFieldOpen :: forall dt name new st. InstrSetFieldC dt name => Instr '[new, ToT (GetFieldType dt name)] '[ToT (GetFieldType dt name)] -> Label name -> Instr (new ': (ToT dt ': st)) (ToT dt ': st)
- instrConstruct :: forall dt st. InstrConstructC dt => Rec (FieldConstructor st) (ConstructorFieldTypes dt) -> Instr st (ToT dt ': st)
- instrConstructStack :: forall dt stack st. (InstrConstructC dt, stack ~ ToTs (ConstructorFieldTypes dt)) => Instr (stack ++ st) (ToT dt ': st)
- instrDeconstruct :: forall dt stack (st :: [T]). (InstrDeconstructC dt st, stack ~ ToTs (GFieldTypes (GRep dt) '[])) => Instr (ToT dt ': st) (stack ++ st)
- type InstrDeconstructC dt st = (GenericIsoValue dt, GInstrDeconstruct (GRep dt) '[] st)
- type GetFieldType dt name = LnrFieldType (GetNamed name dt)
- type family GFieldTypes x rest :: [Type]
- type family GLookupNamed (name :: Symbol) (x :: Type -> Type) :: Maybe LookupNamedResult where ...
- type ConstructorFieldTypes dt = GFieldTypes (GRep dt) '[]
- type ConstructorFieldNames dt = GFieldNames (GRep dt)
- newtype FieldConstructor (st :: [k]) (field :: Type) = FieldConstructor (Instr (ToTs' st) (ToT field ': ToTs' st))
- class ToTs xs ~ ToTs ys => CastFieldConstructors xs ys where
- castFieldConstructorsImpl :: Rec (FieldConstructor st) xs -> Rec (FieldConstructor st) ys
Documentation
type InstrGetFieldC dt name = (GenericIsoValue dt, GInstrGet name (GRep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt))) Source #
Constraint for instrGetField
.
type InstrSetFieldC dt name = (GenericIsoValue dt, GInstrSetField name (GRep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt))) Source #
Constraint for instrSetField
.
type InstrConstructC dt = (GenericIsoValue dt, GInstrConstruct (GRep dt) '[]) Source #
Constraint for instrConstruct
and gInstrConstructStack
.
instrToField :: forall dt name st. InstrGetFieldC dt name => Label name -> Instr (ToT dt ': st) (ToT (GetFieldType dt name) ': st) Source #
Make an instruction which accesses given field of the given datatype.
>>>
pretty $ instrToField @("foo" :! Bool, "bar" :! ()) #foo
[CAR]
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
pretty $ instrToField @Foo #fooField1
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving (Generic, IsoValue)
>>>
pretty $ instrToField @Foo #fooField1
[CAR]
instrGetField :: forall dt name st. (InstrGetFieldC dt name, DupableScope (ToT (GetFieldType dt name))) => Label name -> Instr (ToT dt ': st) (ToT (GetFieldType dt name) ': (ToT dt ': st)) Source #
Make an instruction which copies given field of the given datatype.
This behaves exactly as Seq DUP (instrToField #name)
, but does not require
the entire datatype to be dupable (the field ofc still must be dupable).
If we follow the path from the root to the copied field in the pairs tree, the more nodes contain non-dupable elements in the subtree, the less efficient this function becomes. Assuming that all fields are accessed equally often, the most optimal representation would be to put all dupable elements to one subtree of the root, and all non-dupable elements in the second subtree of the root.
>>>
pretty $ instrGetField @("foo" :! Bool, "bar" :! ()) #foo
[DUP, CAR]
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
pretty $ instrGetField @Foo #fooField1
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving (Generic, IsoValue)
>>>
pretty $ instrGetField @Foo #fooField1
[DUP, CAR]
instrGetFieldOpen :: forall dt name res st. InstrGetFieldC dt name => Instr '[ToT (GetFieldType dt name)] '[res, ToT (GetFieldType dt name)] -> Instr '[ToT (GetFieldType dt name)] '[res] -> Label name -> Instr (ToT dt ': st) (res ': (ToT dt ': st)) Source #
"Open" version of instrGetField
, meaning that it accepts
continuations that accept the copied field. This allows chaining
getters without requiring DupableScope
on the intermediate fields.
Accepted continuations:
- The one that leaves the field on stack (and does a duplication inside). Used when the datatype had an unfortunate placement of non-dupable fields, or the intermediate field contains non-dupable elements, so the duplication cannot occur automatically in between.
- The one that consumes the field, used in case we managed to call
DUP
earlier to make the instruction's implementation smaller, and now we only need to access the field withCAR
andCDR
s.
Note that only one continuation will be chosen eventually, no contract size overhead is expected in this regard.
instrSetField :: forall dt name st. InstrSetFieldC dt name => Label name -> Instr (ToT (GetFieldType dt name) ': (ToT dt ': st)) (ToT dt ': st) Source #
For given complex type dt
and its field fieldTy
update the field value.
>>>
pretty $ instrSetField @("foo" :! Bool, "bar" :! ()) #foo
[DIP { UNPAIR }, DIP { DROP }, PAIR]
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
pretty $ instrSetField @Foo #fooField1
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving (Generic, IsoValue)
>>>
pretty $ instrSetField @Foo #fooField1
[DIP { UNPAIR }, DIP { DROP }, PAIR]
instrSetFieldOpen :: forall dt name new st. InstrSetFieldC dt name => Instr '[new, ToT (GetFieldType dt name)] '[ToT (GetFieldType dt name)] -> Label name -> Instr (new ': (ToT dt ': st)) (ToT dt ': st) Source #
"Open" version of instrSetField
, meaning that it accepts a continuation
that describes how to update the field. This allows chaining setters with
zero overhead and without requiring DupableScope
on the intermediate fields
(if we supported only closed setters that work directly with one datatype, we
would need to duplicate intermediate fields to chain setters).
instrConstruct :: forall dt st. InstrConstructC dt => Rec (FieldConstructor st) (ConstructorFieldTypes dt) -> Instr st (ToT dt ': st) Source #
For given complex type dt
and its field fieldTy
update the field value.
instrConstructStack :: forall dt stack st. (InstrConstructC dt, stack ~ ToTs (ConstructorFieldTypes dt)) => Instr (stack ++ st) (ToT dt ': st) Source #
Construct a complex datatype from values on stack
>>>
pretty $ instrConstructStack @("foo" :! Bool, "bar" :! ())
[DIP { }, PAIR]
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
pretty $ instrConstructStack @Foo
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving (Generic, IsoValue)
>>>
pretty $ instrConstructStack @Foo
[DIP { }, PAIR]
instrDeconstruct :: forall dt stack (st :: [T]). (InstrDeconstructC dt st, stack ~ ToTs (GFieldTypes (GRep dt) '[])) => Instr (ToT dt ': st) (stack ++ st) Source #
For given complex type dt
deconstruct it to its field types.
>>>
pretty $ instrDeconstruct @("foo" :! Bool, "bar" :! ())
[UNPAIR, DIP { }]
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
pretty $ instrDeconstruct @Foo
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving (Generic, IsoValue)
>>>
pretty $ instrDeconstruct @Foo
[UNPAIR, DIP { }]
type InstrDeconstructC dt st = (GenericIsoValue dt, GInstrDeconstruct (GRep dt) '[] st) Source #
Constraint for instrConstruct
.
type GetFieldType dt name = LnrFieldType (GetNamed name dt) Source #
Get type of field by datatype it is contained in and field name.
>>>
() :: GetFieldType ("foo" :! Bool, "bar" :! ()) "bar"
()
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () }
>>>
() :: GetFieldType Foo "fooField2"
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo { fooField1 :: Bool, fooField2 :: () } deriving Generic
>>>
() :: GetFieldType Foo "fooField2"
()
type family GFieldTypes x rest :: [Type] Source #
Instances
type GFieldTypes (U1 :: Type -> Type) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product | |
type GFieldTypes (V1 :: Type -> Type) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product | |
type GFieldTypes (Rec0 a) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product | |
type GFieldTypes (x :*: y) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product | |
type GFieldTypes (x :+: y) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product | |
type GFieldTypes (M1 t i x) rest Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product |
type family GLookupNamed (name :: Symbol) (x :: Type -> Type) :: Maybe LookupNamedResult where ... Source #
GLookupNamed name (D1 _ x) = GLookupNamed name x | |
GLookupNamed name (C1 _ x) = GLookupNamed name x | |
GLookupNamed name (S1 ('MetaSel ('Just recName) _ _ _) (Rec0 a)) = If (name == recName) ('Just $ 'LNR a '[]) 'Nothing | |
GLookupNamed name (S1 _ (Rec0 (NamedF f a fieldName))) = If (name == fieldName) ('Just $ 'LNR (NamedInner (NamedF f a fieldName)) '[]) 'Nothing | |
GLookupNamed _ (S1 _ _) = 'Nothing | |
GLookupNamed name (x :*: y) = LNMergeFound name (GLookupNamed name x) (GLookupNamed name y) | |
GLookupNamed name (_ :+: _) = TypeError (('Text "Cannot seek for a field " ':<>: 'ShowType name) ':<>: 'Text " in sum type") | |
GLookupNamed _ U1 = 'Nothing | |
GLookupNamed _ V1 = TypeError ('Text "Cannot access fields of void-like type") |
type ConstructorFieldTypes dt = GFieldTypes (GRep dt) '[] Source #
Types of all fields in a datatype.
type ConstructorFieldNames dt = GFieldNames (GRep dt) Source #
Names of all fields in a datatype.
newtype FieldConstructor (st :: [k]) (field :: Type) Source #
Way to construct one of the fields in a complex datatype.
FieldConstructor (Instr (ToTs' st) (ToT field ': ToTs' st)) |
class ToTs xs ~ ToTs ys => CastFieldConstructors xs ys where Source #
Ability to pass list of fields with the same ToTs. It may be useful if you don't want to work with NamedF in ConstructorFieldTypes.
castFieldConstructorsImpl :: Rec (FieldConstructor st) xs -> Rec (FieldConstructor st) ys Source #
Instances
CastFieldConstructors ('[] :: [Type]) ('[] :: [Type]) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product castFieldConstructorsImpl :: forall {k} (st :: [k]). Rec (FieldConstructor st) '[] -> Rec (FieldConstructor st) '[] Source # | |
(CastFieldConstructors xs ys, ToTs xs ~ ToTs ys, ToT x ~ ToT y) => CastFieldConstructors (x ': xs) (y ': ys) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Instr.Product castFieldConstructorsImpl :: forall {k} (st :: [k]). Rec (FieldConstructor st) (x ': xs) -> Rec (FieldConstructor st) (y ': ys) Source # |