lorentz-0.14.1: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.UParam

Synopsis

Documentation

newtype UParam (entries :: [EntrypointKind]) Source #

Encapsulates parameter for one of entry points. It keeps entrypoint name and corresponding argument serialized.

In Haskell world, we keep an invariant of that contained value relates to one of entry points from entries list.

Constructors

UnsafeUParam (MText, ByteString) 

Instances

Instances details
Generic (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type Rep (UParam entries) :: Type -> Type #

Methods

from :: UParam entries -> Rep (UParam entries) x #

to :: Rep (UParam entries) x -> UParam entries #

Show (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

showsPrec :: Int -> UParam entries -> ShowS #

show :: UParam entries -> String #

showList :: [UParam entries] -> ShowS #

Eq (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

(==) :: UParam entries -> UParam entries -> Bool #

(/=) :: UParam entries -> UParam entries -> Bool #

HasAnnotation (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Unwrappable (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type Unwrappabled (UParam entries) Source #

HasRPCRepr (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type AsRPC (UParam entries)

Typeable interface => TypeHasDoc (UParam interface) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type TypeDocFieldDescriptions (UParam interface) :: FieldDescriptions #

Methods

typeDocName :: Proxy (UParam interface) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (UParam interface) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (UParam interface) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (UParam interface) #

typeDocMichelsonRep :: TypeDocMichelsonRep (UParam interface) #

IsoValue (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type ToT (UParam entries) :: T #

Methods

toVal :: UParam entries -> Value (ToT (UParam entries)) #

fromVal :: Value (ToT (UParam entries)) -> UParam entries #

SameEntries entries1 entries2 => CanCastTo (UParam entries1 :: Type) (UParam entries2 :: Type) Source #

Allows casts only between UParam_ and UParam.

Instance details

Defined in Lorentz.UParam

Methods

castDummy :: Proxy (UParam entries1) -> Proxy (UParam entries2) -> () Source #

type Rep (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

type Rep (UParam entries) = D1 ('MetaData "UParam" "Lorentz.UParam" "lorentz-0.14.1-inplace" 'True) (C1 ('MetaCons "UnsafeUParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MText, ByteString))))
type Unwrappabled (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

type Unwrappabled (UParam entries)
type AsRPC (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

type AsRPC (UParam entries) = UParam entries
type TypeDocFieldDescriptions (UParam interface) Source # 
Instance details

Defined in Lorentz.UParam

type TypeDocFieldDescriptions (UParam interface) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
type ToT (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

type ToT (UParam entries) = GValueType (Rep (UParam entries))

type EntrypointKind = (Symbol, Type) Source #

An entrypoint is described by two types: its name and type of argument.

type (?:) (n :: Symbol) (a :: k) = '(n, a) Source #

A convenient alias for type-level name-something pair.

Construction

mkUParam :: (NicePackedValue a, LookupEntrypoint name entries ~ a, RequireUniqueEntrypoints entries) => Label name -> a -> UParam entries Source #

Construct a UParam safely.

Deconstruction

data ConstrainedSome (c :: Type -> Constraint) where Source #

This type can store any value that satisfies a certain constraint.

Constructors

ConstrainedSome :: c a => a -> ConstrainedSome c 

Instances

Instances details
Show (ConstrainedSome Show) Source # 
Instance details

Defined in Lorentz.UParam

Buildable (ConstrainedSome Buildable) Source # 
Instance details

Defined in Lorentz.UParam

class UnpackUParam (c :: Type -> Constraint) entries Source #

This class is needed to implement unpackUParam.

Minimal complete definition

unpackUParam

Instances

Instances details
UnpackUParam c ('[] :: [EntrypointKind]) Source # 
Instance details

Defined in Lorentz.UParam

(KnownSymbol name, UnpackUParam c entries, NiceUnpackedValue arg, c arg) => UnpackUParam c ((name ?: arg) ': entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

unpackUParam :: UParam ((name ?: arg) ': entries) -> Either EntrypointLookupError (MText, ConstrainedSome c) Source #

unpackUParam :: UnpackUParam c entries => UParam entries -> Either EntrypointLookupError (MText, ConstrainedSome c) Source #

Turn UParam into a Haskell value. Since we don't know its type in compile time, we have to erase it using ConstrainedSome. The user of this function can require arbitrary constraint to hold (depending on how they want to use the result).

Casting to homomorphic value

type SomeInterface = '['("SomeEntrypoints", Void)] Source #

Pseudo value for UParam type variable.

type UParam_ = UParam SomeInterface Source #

Homomorphic version of UParam, forgets the exact interface.

Pattern-matching

type EntrypointsImpl inp out entries = Rec (CaseClauseU inp out) entries Source #

Implementations of some entry points.

Note that this thing inherits properties of Rec, e.g. you can Data.Vinyl.Core.rappend implementations for two entrypoint sets when assembling scattered parts of a contract.

type UParamFallback inp out = ((MText, ByteString) ': inp) :-> out Source #

An action invoked when user-provided entrypoint is not found.

class CaseUParam (entries :: [EntrypointKind]) Source #

Make up a "case" over entry points.

Minimal complete definition

unsafeCaseUParam

Instances

Instances details
CaseUParam ('[] :: [EntrypointKind]) Source # 
Instance details

Defined in Lorentz.UParam

Methods

unsafeCaseUParam :: forall (inp :: [Type]) (out :: [Type]). Rec (CaseClauseU inp out) '[] -> UParamFallback inp out -> (UParam '[] ': inp) :-> out

(KnownSymbol name, CaseUParam entries, Typeable entries, NiceUnpackedValue arg) => CaseUParam ((name ?: arg) ': entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

unsafeCaseUParam :: forall (inp :: [Type]) (out :: [Type]). Rec (CaseClauseU inp out) ((name ?: arg) ': entries) -> UParamFallback inp out -> (UParam ((name ?: arg) ': entries) ': inp) :-> out

caseUParam :: (CaseUParam entries, RequireUniqueEntrypoints entries) => Rec (CaseClauseU inp out) entries -> UParamFallback inp out -> (UParam entries ': inp) :-> out Source #

Pattern-match on given UParam entries.

You have to provide all case branches and a fallback action on case when entrypoint is not found.

caseUParamT :: forall entries inp out clauses. (clauses ~ Rec (CaseClauseU inp out) entries, RecFromTuple clauses, CaseUParam entries) => IsoRecTuple clauses -> UParamFallback inp out -> (UParam entries ': inp) :-> out Source #

Like caseUParam, but accepts a tuple of clauses, not a Rec.

uparamFallbackFail :: UParamFallback inp out Source #

Default implementation for UParamFallback, simply reports an error.

Constraints

type family LookupEntrypoint (name :: Symbol) (entries :: [EntrypointKind]) :: Type where ... Source #

Get type of entrypoint argument by its name.

Equations

LookupEntrypoint name ('(name, a) ': _) = a 
LookupEntrypoint name (_ ': entries) = LookupEntrypoint name entries 
LookupEntrypoint name '[] = TypeError (('Text "Entry point " :<>: 'ShowType name) :<>: 'Text " in not in the entry points list") 

type family RequireUniqueEntrypoints (entries :: [EntrypointKind]) :: Constraint where ... Source #

Ensure that given entry points do no contain duplicated names.

Equations

RequireUniqueEntrypoints entries = RequireAllUnique "entrypoint" (Eval (Map Fst entries)) 

Conversion from ADT

uparamFromAdt :: UParamLinearize up => up -> UParam (UParamLinearized up) Source #

Make up UParam from ADT sum.

Entry points template will consist of (constructorName, constructorFieldType) pairs. Each constructor is expected to have exactly one field.

type UParamLinearize p = (Generic p, GUParamLinearize (Rep p)) Source #

Constraint required by uparamFromAdt.

type UParamLinearized p = GUParamLinearized (Rep p) Source #

Entry points template derived from given ADT sum.

Documentation

pbsUParam :: forall ctorName. KnownSymbol ctorName => ParamBuildingStep Source #

Note that calling given entrypoints involves constructing UParam.

Internals used for entrypoint-wise migrations

unwrapUParam :: (UParam entries ': s) :-> ((MText, ByteString) ': s) Source #

Helper instruction which extracts content of UParam.

Orphan instances

CustomErrorHasDoc "uparamArgumentUnpackFailed" Source # 
Instance details

CustomErrorHasDoc "uparamNoSuchEntrypoint" Source # 
Instance details

Buildable (CustomError "uparamArgumentUnpackFailed") Source # 
Instance details

Methods

build :: CustomError "uparamArgumentUnpackFailed" -> Builder #

Buildable (CustomError "uparamNoSuchEntrypoint") Source # 
Instance details

Methods

build :: CustomError "uparamNoSuchEntrypoint" -> Builder #