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

Lorentz.EntryPoints

Description

Entrypoints utilities for Lorentz

Synopsis

Typeclasses

class EntryPointsDerivation deriv cp where Source #

Defines a generalized way to declare entrypoints for various parameter types.

When defining instances of this typeclass, set concrete deriv argument and leave variable cp argument. Also keep in mind, that in presence of explicit default entrypoint, all other Or arms should be callable, though you can put this burden on user if very necessary.

Methods of this typeclass aim to better type-safety when making up an implementation and they may be not too convenient to use; users should exploit their counterparts.

Associated Types

type EpdAllEntryPoints deriv cp :: [(Symbol, Type)] Source #

Name and argument of each entrypoint. This may include intermediate ones, even root if necessary.

Touching this type family is costly (O(N^2)), don't use it often.

Note [order of entrypoints children]: If this contains entrypoints referring to indermediate nodes (not leaves) in or tree, then each such entrypoint should be mentioned eariler than all of its children.

type EpdLookupEntryPoint deriv cp :: Symbol -> Exp (Maybe Type) Source #

Get entrypoint argument by name.

Methods

epdNotes :: Notes (ToT cp) Source #

Construct parameter annotations corresponding to expected entrypoints set.

This method is implementation detail, for actual notes construction use parameterEntryPointsToNotes.

TODO [#35]: Should also return field annotation

epdCall :: ParameterScope (ToT cp) => Label name -> EpConstructionRes (ToT cp) (Eval (EpdLookupEntryPoint deriv cp name)) Source #

Construct entrypoint caller.

This does not treat calls to default entrypoint in a special way.

This method is implementation detail, for actual entrypoint lookup use parameterEntryPointCall.

epdDescs :: Rec EpCallingDesc (EpdAllEntryPoints deriv cp) Source #

Description of how each of the entrypoints is constructed.

Instances

Instances details
HasTypeAnn cp => EntryPointsDerivation EpdNone cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

PlainEntryPointsC EpdDelegate cp => EntryPointsDerivation EpdDelegate cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Impl

PlainEntryPointsC EpdRecursive cp => EntryPointsDerivation EpdRecursive cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Impl

PlainEntryPointsC EpdPlain cp => EntryPointsDerivation EpdPlain cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Impl

class (EntryPointsDerivation (ParameterEntryPointsDerivation cp) cp, RequireAllUniqueEntryPoints cp) => ParameterHasEntryPoints cp Source #

Which entrypoints given parameter declares.

Note that usually this function should not be used as constraint, use ParameterDeclaresEntryPoints for this purpose.

Associated Types

type ParameterEntryPointsDerivation cp :: Type Source #

Instances

Instances details
(NiceParameter cp, EntryPointsDerivation epd cp, RequireAllUniqueEntryPoints' epd cp) => ParameterHasEntryPoints (ParameterWrapper epd cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

type ParameterDeclaresEntryPoints cp = (If (CanHaveEntryPoints cp) (ParameterHasEntryPoints cp) (() :: Constraint), NiceParameter cp, EntryPointsDerivation (GetParameterEpDerivation cp) cp) Source #

Parameter declares some entrypoints.

This is a version of ParameterHasEntryPoints which we actually use in constraints. When given type is a sum type or newtype, we refer to ParameterHasEntryPoints instance, otherwise this instance is not necessary.

Entrypoints API

type family AllParameterEntryPoints (cp :: Type) :: [(Symbol, Type)] where ... Source #

Get all entrypoints declared for parameter.

type family LookupParameterEntryPoint (cp :: Type) :: Symbol -> Exp (Maybe Type) where ... Source #

Lookup for entrypoint type by name.

Does not treat default entrypoints in a special way.

parameterEntryPointsToNotes :: forall cp. ParameterDeclaresEntryPoints cp => ParamNotes (ToT cp) Source #

Derive annotations for given parameter.

type GetEntryPointArg cp name = Eval (LiftM2 FromMaybe (TError (('Text "Entrypoint not found: " :<>: 'ShowType name) :$$: (('Text "In contract parameter `" :<>: 'ShowType cp) :<>: 'Text "`"))) (LookupParameterEntryPoint cp name)) Source #

Get type of entrypoint with given name, fail if not found.

parameterEntryPointCall :: forall cp name. ParameterDeclaresEntryPoints cp => Label name -> EntryPointCall cp (GetEntryPointArg cp name) Source #

Prepare call to given entrypoint.

This does not treat calls to default entrypoint in a special way. To call default entrypoint properly use parameterEntryPointCallDefault.

type GetDefaultEntryPointArg cp = Eval (LiftM2 FromMaybe (Pure cp) (LookupParameterEntryPoint cp DefaultEpName)) Source #

Get type of entrypoint with given name, fail if not found.

type ForbidExplicitDefaultEntryPoint cp = Eval (LiftM3 UnMaybe (Pure (Pure (() :: Constraint))) (TError ('Text "Parameter used here must have no explicit \"default\" entrypoint" :$$: (('Text "In parameter type `" :<>: 'ShowType cp) :<>: 'Text "`"))) (LookupParameterEntryPoint cp DefaultEpName)) Source #

Ensure that there is no explicit "default" entrypoint.

type NoExplicitDefaultEntryPoint cp = Eval (LookupParameterEntryPoint cp DefaultEpName) ~ 'Nothing Source #

Similar to ForbidExplicitDefaultEntryPoint, but in a version which the compiler can work with (and which produces errors confusing for users :/)

sepcCallRootChecked :: forall cp. (NiceParameter cp, ForbidExplicitDefaultEntryPoint cp) => SomeEntryPointCall cp Source #

Call root entrypoint safely.

data EntryPointRef (mname :: Maybe Symbol) where Source #

Which entrypoint to call.

We intentionally distinguish default and non-default cases because this makes API more details-agnostic.

Constructors

CallDefault :: EntryPointRef 'Nothing

Call the default entrypoint, or root if no explicit default is assigned.

Call :: NiceEntryPointName name => EntryPointRef ('Just name)

Call the given entrypoint; calling default is not treated specially. You have to provide entrypoint name via passing it as type argument.

Unfortunatelly, here we cannot accept a label because in most cases our entrypoints begin from capital letter (being derived from constructor name), while labels must start from a lower-case letter, and there is no way to make a conversion at type-level.

Instances

Instances details
(GetEntryPointArgCustom cp mname ~ arg, ParameterDeclaresEntryPoints cp) => HasEntryPointArg (cp :: Type) (EntryPointRef mname) arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

eprName :: forall mname. EntryPointRef mname -> EpName Source #

type family GetEntryPointArgCustom cp mname :: Type where ... Source #

Universal entrypoint lookup.

class HasEntryPointArg cp name arg where Source #

When we call a Lorentz contract we should pass entrypoint name and corresponding argument. Ideally we want to statically check that parameter has entrypoint with given name and argument. Constraint defined by this type class holds for contract with parameter cp that have entrypoint matching name with type arg.

In order to check this property statically, we need to know entrypoint name in compile time, EntryPointRef type serves this purpose. If entrypoint name is not known, one can use TrustEpName wrapper to take responsibility for presence of this entrypoint.

If you want to call a function which has this constraint, you have two options: 1. Pass contract parameter cp using type application, pass EntryPointRef as a value and pass entrypoint argument. Type system will check that cp has an entrypoint with given reference and type. 2. Pass EpName wrapped into TrustEpName and entrypoint argument. In this case passing contract parameter is not necessary, you do not even have to know it.

Methods

useHasEntryPointArg :: name -> (Dict (ParameterScope (ToT arg)), EpName) Source #

Data returned by this method may look somewhat arbitrary. EpName is obviously needed because name can be EntryPointRef or TrustEpName. Dict is returned because in EntryPointRef case we get this evidence for free and don't want to use it. We seem to always need it anyway.

Instances

Instances details
NiceParameter arg => HasEntryPointArg (cp :: k) TrustEpName arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

(GetEntryPointArgCustom cp mname ~ arg, ParameterDeclaresEntryPoints cp) => HasEntryPointArg (cp :: Type) (EntryPointRef mname) arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

type HasDefEntryPointArg cp defEpName defArg = (defEpName ~ EntryPointRef 'Nothing, HasEntryPointArg cp defEpName defArg) Source #

HasEntryPointArg constraint specialized to default entrypoint.

type HasEntryPointOfType param con exp = (GetEntryPointArgCustom param ('Just con) ~ exp, ParameterDeclaresEntryPoints param) Source #

Checks that the given parameter consists of some specific entrypoint. Similar as HasEntryPointArg but ensures that the argument matches the following datatype.

type family ParameterContainsEntryPoints param (fields :: [NamedEp]) :: Constraint where ... Source #

Check that the given entrypoint has some fields inside. This interface allows for an abstraction of contract parameter so that it requires some *minimal* specification, but not a concrete one.

Equations

ParameterContainsEntryPoints _ '[] = () 
ParameterContainsEntryPoints param ((n :> ty) ': rest) = (HasEntryPointOfType param n ty, ParameterContainsEntryPoints param rest) 

newtype TrustEpName Source #

This wrapper allows to pass untyped EpName and bypass checking that entrypoint with given name and type exists.

Constructors

TrustEpName EpName 

Instances

Instances details
NiceParameter arg => HasEntryPointArg (cp :: k) TrustEpName arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

parameterEntryPointCallCustom :: forall cp mname. ParameterDeclaresEntryPoints cp => EntryPointRef mname -> EntryPointCall cp (GetEntryPointArgCustom cp mname) Source #

Universal entrypoint calling.

type RequireAllUniqueEntryPoints cp = RequireAllUniqueEntryPoints' (ParameterEntryPointsDerivation cp) cp Source #

Ensure that all declared entrypoints are unique.

type (:>) n ty = 'NamedEp n ty infixr 0 Source #

Implementations

data EpdNone Source #

No entrypoints declared, parameter type will serve as argument type of the only existing entrypoint (default one).

Instances

Instances details
HasTypeAnn cp => EntryPointsDerivation EpdNone cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

type EpdAllEntryPoints EpdNone cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

type EpdAllEntryPoints EpdNone cp = '[] :: [(Symbol, Type)]
type EpdLookupEntryPoint EpdNone cp Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

data EpdPlain Source #

Implementation of ParameterHasEntryPoints which fits for case when your contract exposes multiple entrypoints via having sum type as its parameter.

In particular, each constructor would produce a homonymous entrypoint with argument type equal to type of constructor field (each constructor should have only one field). Constructor called Default will designate the default entrypoint.

data EpdRecursive Source #

Extension of EpdPlain on parameters being defined as several nested datatypes.

In particular, this will traverse sum types recursively, stopping at Michelson primitives (like Natural) and constructors with number of fields different from one.

It does not assign names to intermediate nodes of Or tree, only to the very leaves.

If some entrypoint arguments have custom IsoValue instance, this derivation way will not work. As a workaround, you can wrap your argument into some primitive (e.g. :!).

data EpdDelegate Source #

Extension of EpdPlain on parameters being defined as several nested datatypes.

In particular, it will traverse the immediate sum type, and require another ParameterHasEntryPoints for the inner complex datatypes. Only those inner types are considered which are the only fields in their respective constructors. Inner types should not themselves declare default entrypoint, we enforce this for better modularity. Each top-level constructor will be treated as entrypoint even if it contains a complex datatype within, in such case that would be an entrypoint corresponding to intermediate node in or tree.

Comparing to EpdRecursive this gives you more control over where and how entrypoints will be derived.

Behaviour modifiers

newtype ParameterWrapper (deriv :: Type) cp Source #

Wrap parameter into this to locally assign a way to derive entrypoints for it.

Constructors

ParameterWrapper 

Fields

Instances

Instances details
Generic (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

Associated Types

type Rep (ParameterWrapper deriv cp) :: Type -> Type #

Methods

from :: ParameterWrapper deriv cp -> Rep (ParameterWrapper deriv cp) x #

to :: Rep (ParameterWrapper deriv cp) x -> ParameterWrapper deriv cp #

Wrapped (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

Associated Types

type Unwrapped (ParameterWrapper deriv cp) #

Methods

_Wrapped' :: Iso' (ParameterWrapper deriv cp) (Unwrapped (ParameterWrapper deriv cp)) #

IsoValue cp => IsoValue (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

Associated Types

type ToT (ParameterWrapper deriv cp) :: T #

Methods

toVal :: ParameterWrapper deriv cp -> Value (ToT (ParameterWrapper deriv cp)) #

fromVal :: Value (ToT (ParameterWrapper deriv cp)) -> ParameterWrapper deriv cp #

(NiceParameter cp, EntryPointsDerivation epd cp, RequireAllUniqueEntryPoints' epd cp) => ParameterHasEntryPoints (ParameterWrapper epd cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

type Rep (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

type Rep (ParameterWrapper deriv cp) = D1 ('MetaData "ParameterWrapper" "Lorentz.EntryPoints.Manual" "lorentz-0.4.0-4bB2PLHB7038abCZLw1vnA" 'True) (C1 ('MetaCons "ParameterWrapper" 'PrefixI 'True) (S1 ('MetaSel ('Just "unParameterWraper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 cp)))
type Unwrapped (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

type Unwrapped (ParameterWrapper deriv cp) = GUnwrapped (Rep (ParameterWrapper deriv cp))
type ToT (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

type ToT (ParameterWrapper deriv cp) = GValueType (Rep (ParameterWrapper deriv cp))
type ParameterEntryPointsDerivation (ParameterWrapper epd cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

newtype ShouldHaveEntryPoints a Source #

A special type which wraps over a primitive type and states that it has entrypoints (one).

Assuming that any type can have entrypoints makes use of Lorentz entrypoints too annoying, so for declaring entrypoints for not sum types we require an explicit wrapper.

Constructors

ShouldHaveEntryPoints 

Fields

Instances

Instances details
Generic (ShouldHaveEntryPoints a) Source # 
Instance details

Defined in Lorentz.EntryPoints.Helpers

Associated Types

type Rep (ShouldHaveEntryPoints a) :: Type -> Type #

WellTypedIsoValue r => IsoValue (ShouldHaveEntryPoints r) Source # 
Instance details

Defined in Lorentz.EntryPoints.Helpers

Associated Types

type ToT (ShouldHaveEntryPoints r) :: T #

type Rep (ShouldHaveEntryPoints a) Source # 
Instance details

Defined in Lorentz.EntryPoints.Helpers

type Rep (ShouldHaveEntryPoints a) = D1 ('MetaData "ShouldHaveEntryPoints" "Lorentz.EntryPoints.Helpers" "lorentz-0.4.0-4bB2PLHB7038abCZLw1vnA" 'True) (C1 ('MetaCons "ShouldHaveEntryPoints" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHasEntryPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type ToT (ShouldHaveEntryPoints r) Source # 
Instance details

Defined in Lorentz.EntryPoints.Helpers