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

Lorentz.Entrypoints.Helpers

Synopsis

Documentation

ctorNameToAnn :: forall ctor. (KnownSymbol ctor, HasCallStack) => FieldAnn Source #

ctorNameToEp :: forall ctor. (KnownSymbol ctor, HasCallStack) => EpName Source #

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) 

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.6.1-inplace" '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

type family RequireSumType (a :: Type) :: Constraint where ... Source #

Ensure that given type is a sum type.

This helps to prevent attempts to apply a function to, for instance, a pair.

Equations

RequireSumType a = If (CanHaveEntrypoints a) (() :: Constraint) (TypeError ('Text "Expected Michelson sum type" :$$: (('Text "In type `" :<>: 'ShowType a) :<>: 'Text "`")))