morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Typed.Haskell.Instr.Product

Description

Instructions working on product types derived from Haskell ones.

Synopsis

Documentation

type InstrGetFieldC dt name = (GenericIsoValue dt, GInstrGet name (Rep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt))) Source #

Constraint for instrGetField.

type InstrSetFieldC dt name = (GenericIsoValue dt, GInstrSetField name (Rep dt) (LnrBranch (GetNamed name dt)) (LnrFieldType (GetNamed name dt))) Source #

Constraint for instrSetField.

type InstrConstructC dt = (GenericIsoValue dt, GInstrConstruct (Rep 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.

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.

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:

  1. 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.
  2. 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 with CAR and CDRs.

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.

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 #

instrDeconstruct :: forall dt stack (st :: [T]). (InstrDeconstructC dt st, stack ~ ToTs (GFieldTypes (Rep dt) '[])) => Instr (ToT dt ': st) (stack ++ st) Source #

For given complex type dt deconstruct it to its field types.

type InstrDeconstructC dt st = (GenericIsoValue dt, GInstrDeconstruct (Rep 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.

type family GFieldTypes x rest :: [Type] Source #

Instances

Instances details
type GFieldTypes (U1 :: Type -> Type) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (U1 :: Type -> Type) rest = rest
type GFieldTypes (V1 :: Type -> Type) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (V1 :: Type -> Type) rest = '[] :: [Type]
type GFieldTypes (Rec0 a) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (Rec0 a) rest = a ': rest
type GFieldTypes (x :*: y) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (x :*: y) rest = GFieldTypes x (GFieldTypes y rest)
type GFieldTypes (x :+: y) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (x :+: y) rest = '[] :: [Type]
type GFieldTypes (M1 t i x) rest Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

type GFieldTypes (M1 t i x) rest = GFieldTypes x rest

type family GLookupNamed (name :: Symbol) (x :: Type -> Type) :: Maybe LookupNamedResult where ... Source #

Equations

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 (Rep dt) '[] Source #

Types of all fields in a datatype.

type ConstructorFieldNames dt = GFieldNames (Rep 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.

Constructors

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.

Instances

Instances details
CastFieldConstructors ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

Methods

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 # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

Methods

castFieldConstructorsImpl :: forall {k} (st :: [k]). Rec (FieldConstructor st) (x ': xs) -> Rec (FieldConstructor st) (y ': ys) Source #