-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# LANGUAGE UndecidableSuperClasses #-} -- | Scope-related constraints used in Lorentz. -- -- This contains constraints from "Morley.Michelson.Typed.Scope" modified for use -- in Lorentz. module Lorentz.Constraints.Scopes ( -- * Grouped constraints NiceComparable , NiceConstant , Dupable , NiceFullPackedValue , NicePackedValue , NiceParameter , NiceUntypedValue , NiceStorage , NiceStorageFull , NiceUnpackedValue , NiceViewable , NiceNoBigMap , niceParameterEvi , niceStorageEvi , niceConstantEvi , dupableEvi , nicePackedValueEvi , niceUnpackedValueEvi , niceUntypedValueEvi , niceViewableEvi -- * Individual constraints (internals) , CanHaveBigMap , KnownValue , NoOperation , NoContractType , NoBigMap , -- * Re-exports withDict ) where import Data.Constraint (evidence, trans, weaken1) import Lorentz.Annotation (HasAnnotation) import Morley.Michelson.Typed -- We write these constraints as class + instance, rather than -- type aliases, in order to allow their partial application. -- | Gathers constraints, commonly required for values. class (IsoValue a, Typeable a) => KnownValue a instance (IsoValue a, Typeable a) => KnownValue a -- | Ensure given type does not contain "operation". class (ForbidOp (ToT a), IsoValue a) => NoOperation a instance (ForbidOp (ToT a), IsoValue a) => NoOperation a class (ForbidContract (ToT a), IsoValue a) => NoContractType a instance (ForbidContract (ToT a), IsoValue a) => NoContractType a class (ForbidBigMap (ToT a), IsoValue a) => NoBigMap a instance (ForbidBigMap (ToT a), IsoValue a) => NoBigMap a class (HasNoNestedBigMaps (ToT a), IsoValue a) => CanHaveBigMap a instance (HasNoNestedBigMaps (ToT a), IsoValue a) => CanHaveBigMap a -- | Constraint applied to any part of a parameter type. -- -- Use t'Lorentz.Constraints.Derivative.NiceParameterFull' instead -- when you need to know the contract's entrypoints at compile-time. type NiceParameter a = (ProperParameterBetterErrors (ToT a), KnownValue a) type NiceStorage a = (ProperStorageBetterErrors (ToT a), KnownValue a) type NiceStorageFull a = (NiceStorage a, HasAnnotation a) type NiceConstant a = (ProperConstantBetterErrors (ToT a), KnownValue a) type Dupable a = (ProperDupableBetterErrors (ToT a), KnownValue a) type NicePackedValue a = (ProperPackedValBetterErrors (ToT a), KnownValue a) type NiceUnpackedValue a = (ProperUnpackedValBetterErrors (ToT a), KnownValue a) type NiceFullPackedValue a = (NicePackedValue a, NiceUnpackedValue a) type NiceUntypedValue a = (ProperUntypedValBetterErrors (ToT a), KnownValue a) type NiceViewable a = (ProperViewableBetterErrors (ToT a), KnownValue a) -- | Constraint applied to any type, to check if Michelson representation (if exists) of this -- type is Comparable. In case it is not prints human-readable error message type NiceComparable n = (ProperNonComparableValBetterErrors (ToT n), KnownValue n, Comparable (ToT n)) type NiceNoBigMap n = (KnownValue n, HasNoBigMap (ToT n)) niceParameterEvi :: forall a. NiceParameter a :- ParameterScope (ToT a) niceParameterEvi = properParameterEvi @(ToT a) `trans` weaken1 niceStorageEvi :: forall a. NiceStorage a :- StorageScope (ToT a) niceStorageEvi = Sub (evidence $ properStorageEvi @(ToT a)) niceConstantEvi :: forall a. NiceConstant a :- ConstantScope (ToT a) niceConstantEvi = properConstantEvi @(ToT a) `trans` weaken1 dupableEvi :: forall a. Dupable a :- DupableScope (ToT a) dupableEvi = properDupableEvi @(ToT a) `trans` weaken1 nicePackedValueEvi :: forall a. NicePackedValue a :- PackedValScope (ToT a) nicePackedValueEvi = properPackedValEvi @(ToT a) `trans` weaken1 niceUnpackedValueEvi :: forall a. NiceUnpackedValue a :- UnpackedValScope (ToT a) niceUnpackedValueEvi = properUnpackedValEvi @(ToT a) `trans` weaken1 niceUntypedValueEvi :: forall a. NiceUntypedValue a :- UntypedValScope (ToT a) niceUntypedValueEvi = properUntypedValEvi @(ToT a) `trans` weaken1 niceViewableEvi :: forall a. NiceViewable a :- ViewableScope (ToT a) niceViewableEvi = properViewableEvi @(ToT a) `trans` weaken1