lorentz-0.1.0: EDSL for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.EntryPoints.Core

Contents

Description

Primitives supplying entrypoints declarations and lookup.

Synopsis

Documentation

type family CanHaveEntryPoints (p :: Type) :: Bool where ... Source #

Used to understand whether a type can potentially declare any entrypoints.

Equations

CanHaveEntryPoints (ShouldHaveEntryPoints _) = True 
CanHaveEntryPoints p = CanHaveEntryPointsT (ToT p) 

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.

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.

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 :: (KnownSymbol name, 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.

Instances
SingI (ToT 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

data EpConstructionRes (param :: T) (marg :: Maybe Type) where Source #

Result of entrypoint lookup at term level.

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

Ensure that all declared entrypoints are unique.

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 #

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.

type GetParameterEpDerivation cp = If (CanHaveEntryPoints cp) (ParameterEntryPointsDerivation cp) EpdNone Source #

Version of ParameterEntryPointsDerivation which we actually use in function signatures. When given type is sum type or newtype, we refer to ParameterEntryPointsDerivation, otherwise we suppose that no entrypoints are declared.

pepNotes :: forall cp. ParameterDeclaresEntryPoints cp => Notes (ToT cp) Source #

Version of epdNotes which we actually use in code. It hides derivations stuff inside, and treats primitive types specially like GetParameterEpDerivation does.

pepCall :: forall cp name deriv. (ParameterDeclaresEntryPoints cp, ParameterScope (ToT cp), KnownSymbol name, deriv ~ GetParameterEpDerivation cp) => Label name -> EpConstructionRes (ToT cp) (Eval (EpdLookupEntryPoint deriv cp name)) Source #

Version of epdCall which we actually use in code. It hides derivations stuff inside, and treats primitive types specially like GetParameterEpDerivation does.

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. (Typeable 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, KnownSymbol name) => 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.

flattenEntryPoints :: SingI t => ParamNotes t -> Map EpName Type Source #

Flatten a provided list of notes to a map of its entrypoints and its corresponding utype.

It is obtained by constructing `insert k1 v1 (insert k2 v2 ... mempty)` pipe using Endo so that it is more concise rather than stacking composition of monoidal endomorphisms explicitly. Note that here no duplicates can appear in returned map for ParamNotes even if they may appear inside passed Notes tree.

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
(GetEntryPointArgCustom cp mname ~ arg, ParameterDeclaresEntryPoints cp) => HasEntryPointArg (cp :: Type) (EntryPointRef mname) arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

type NiceEntryPointName name = (KnownSymbol name, ForbidDefaultName name) Source #

Constraint on type-level entrypoint name specifier.

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

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

Universal entrypoint lookup.

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
NiceParameter arg => HasEntryPointArg (cp :: k) TrustEpName arg Source # 
Instance details

Defined in Lorentz.EntryPoints.Core

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
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.

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

Universal entrypoint calling.

data EpdNone Source #

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

Instances
SingI (ToT 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

Internals

type RequireAllUniqueEntryPoints' deriv cp = RequireAllUnique "entrypoint name" (Eval (Map Fst $ EpdAllEntryPoints deriv cp)) Source #