lorentz-0.9.0: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Extensible

Description

This module contains implementation of Extensible values.

Extensible values are an alternative representation of sum-types for Michelson. Instead of representing them as nested options, we treat them as (Natural, ByteString) pair, where the first element of the pair represents the constructor index, while the second is a packed argument.

With such a representation sum types can be easily upgraded: it is possible to add new elements to the sum type, and the representation would not change.

However, such representation essentially limits the applicability of the values. This module does not provide Michelson-level function to unwrap the value because it would require traversing all the possible options in the contract code. While this is possible, it is very inefficient. Up to this moment, we have not come up with a decent reason to allow such behavior, so Extensible types are write-only in Michelson code. They can be unwrapped off-chain with fromExtVal.

In order to preserve previous values during migrations, users should ONLY APPEND items to the underlying sum type. Changing, reordering and deleting items is not allowed and would lead to compatibility breakage. Currently, this restriction in not enforced. Only no-argument and one-argument constructors are supported.

GOOD: -- `Extensible GoodSumTypeV1` is backwards compatible -- with `Extensible GoodSumTypeV2` data GoodSumTypeV1 = A Natural | B data GoodSumTypeV2 = A Natural | B | C MText

BAD: -- `Extensible BadSumTypeV1` is NOT backwards compatible -- with `Extensible BadSumTypeV2` data BadSumTypeV1 = A | B data BadSumTypeV2 = A Natural | B | C MText

Synopsis

Documentation

newtype Extensible x Source #

Constructors

Extensible (Natural, ByteString) 

Instances

Instances details
Eq (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Methods

(==) :: Extensible x -> Extensible x -> Bool #

(/=) :: Extensible x -> Extensible x -> Bool #

Show (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Generic (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type Rep (Extensible x) :: Type -> Type #

Methods

from :: Extensible x -> Rep (Extensible x) x0 #

to :: Rep (Extensible x) x0 -> Extensible x #

(ExtensibleHasDoc x, ReifyList DocumentCtor (EnumerateCtors (GetCtors x))) => TypeHasDoc (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type TypeDocFieldDescriptions (Extensible x) :: FieldDescriptions #

IsoValue (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type ToT (Extensible x) :: T #

HasAnnotation (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Wrappable (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type Unwrappable (Extensible x) Source #

type Rep (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

type Rep (Extensible x) = D1 ('MetaData "Extensible" "Lorentz.Extensible" "lorentz-0.9.0-inplace" 'True) (C1 ('MetaCons "Extensible" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Natural, ByteString))))
type TypeDocFieldDescriptions (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

type ToT (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

type ToT (Extensible x) = GValueType (Rep (Extensible x))
type Unwrappable (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

type ExtVal x = (Generic x, GExtVal x (Rep x)) Source #

class Typeable x => ExtensibleHasDoc x where Source #

Information to be provided for documenting some Extensible x.

Minimal complete definition

extensibleDocName, extensibleDocMdDescription

Methods

extensibleDocName :: Proxy x -> Text Source #

Implementation for typeDocName of the corresponding Extensible.

extensibleDocDependencies :: Proxy x -> [SomeDocDefinitionItem] Source #

Implementation for typeDocDependencies of the corresponding Extensible.

default extensibleDocDependencies :: (Generic x, GTypeHasDoc (Rep x)) => Proxy x -> [SomeDocDefinitionItem] Source #

extensibleDocMdDescription :: Markdown Source #

Overall description of this type.

toExtVal :: ExtVal a => a -> Extensible a Source #

Converts a value from a Haskell representation to its extensible Michelson representation (i.e. (Natural, Bytestring) pair).

fromExtVal :: ExtVal a => Extensible a -> Either ExtConversionError a Source #

Converts a value from an extensible Michelson representation to its Haskell sum-type representation. Fails if the Michelson representation points to a nun-existent constructor, or if we failed to unpack the argument.

wrapExt :: forall t (n :: Nat) name field s. WrapExtC t n name field s => Label ("c" `AppendSymbol` name) -> AppendCtorField field s :-> (Extensible t ': s) Source #

Wraps an argument on top of the stack into an Extensible representation

type WrapExtC t n name field s = ('Ctor n name field ~ LookupCtor name (EnumerateCtors (GetCtors t)), WrapExt field, KnownNat n) Source #