-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ module Lorentz.Entrypoints.Helpers ( ctorNameToAnn , ctorNameToEp , CanHaveEntrypoints , ShouldHaveEntrypoints (..) , RequireSumType ) where import qualified Data.Kind as Kind import Michelson.Typed.Haskell import Michelson.Typed.T import Michelson.Untyped (EpName, FieldAnn, ann, epNameFromParamAnn) import Util.Text import Util.Type import Util.TypeLits ctorNameToAnn :: forall ctor. (KnownSymbol ctor, HasCallStack) => FieldAnn ctorNameToAnn = ann . headToLower $ (symbolValT' @ctor) ctorNameToEp :: forall ctor. (KnownSymbol ctor, HasCallStack) => EpName ctorNameToEp = epNameFromParamAnn (ctorNameToAnn @ctor) ?: error "Empty constructor-entrypoint name" -- | 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. newtype ShouldHaveEntrypoints a = ShouldHaveEntrypoints { unHasEntrypoints :: a } deriving stock Generic deriving anyclass instance (WellTypedIsoValue r) => IsoValue (ShouldHaveEntrypoints r) -- | Used to understand whether a type can potentially declare any entrypoints. type family CanHaveEntrypoints (p :: Kind.Type) :: Bool where CanHaveEntrypoints (ShouldHaveEntrypoints _) = 'True CanHaveEntrypoints p = CanHaveEntrypointsT (ToT p) type family CanHaveEntrypointsT (t :: T) :: Bool where CanHaveEntrypointsT ('TOr _ _) = 'True CanHaveEntrypointsT _ = 'False -- | Ensure that given type is a sum type. -- -- This helps to prevent attempts to apply a function to, for instance, a pair. type family RequireSumType (a :: Kind.Type) :: Constraint where RequireSumType a = If (CanHaveEntrypoints a) (() :: Constraint) (TypeError ('Text "Expected Michelson sum type" ':$$: 'Text "In type `" ':<>: 'ShowType a ':<>: 'Text "`" ))