morley-1.16.0: Developer tools for the Michelson Language
Safe HaskellNone
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 instrToField.

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.

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.

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), KnownList stack) => Instr (stack ++ st) (ToT dt ': st) Source #

instrDeconstruct :: forall dt stack st. (InstrDeconstructC dt, stack ~ ToTs (ConstructorFieldTypes dt), KnownList stack) => Instr (ToT dt ': st) (stack ++ st) Source #

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

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