-- SPDX-FileCopyrightText: 2021 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ module Morley.Michelson.Typed.Existential ( SomeConstant (..) , SomeConstrainedValue (..) , SomeContract (..) , SomeContractAndStorage (..) , SomeIsoValue (..) , SomeValue (..) , SomeStorage(..) ) where import Fmt (Buildable(..)) import Morley.Michelson.Printer.Util (RenderDoc(..)) import Morley.Michelson.Typed.Aliases import Morley.Michelson.Typed.Convert () import Morley.Michelson.Typed.Haskell.Value (KnownIsoT) import Morley.Michelson.Typed.Scope import Morley.Michelson.Typed.T (T(..)) import Morley.Util.Sing (eqParamSing) data SomeConstrainedValue (c :: T -> Constraint) where SomeConstrainedValue :: forall (t :: T) (c :: T -> Constraint) . (c t) => Value t -> SomeConstrainedValue c deriving stock instance Show (SomeConstrainedValue c) -- TODO -- @gromak: perhaps we should implement `SomeValue` in terms of -- `SomeConstrainedValue`, but it will require changing quite a lot of code, -- so it is postponed. data SomeValue where SomeValue :: SingI t => Value t -> SomeValue deriving stock instance Show SomeValue instance Eq SomeValue where SomeValue v1 == SomeValue v2 = v1 `eqParamSing` v2 data SomeConstant where SomeConstant :: (ConstantScope t, SingI t) => Value t -> SomeConstant instance Buildable SomeConstant where build (SomeConstant v) = build v instance RenderDoc SomeConstant where renderDoc pn (SomeConstant v) = renderDoc pn v -- | Hides some Haskell value put in line with Michelson 'Value'. data SomeIsoValue where SomeIsoValue :: (KnownIsoT a) => a -> SomeIsoValue data SomeContract where SomeContract :: Contract cp st -> SomeContract instance NFData SomeContract where rnf (SomeContract c) = rnf c deriving stock instance Show SomeContract -- | Represents a typed contract & a storage value of the type expected by the contract. data SomeContractAndStorage where SomeContractAndStorage :: forall cp st. (StorageScope st, ParameterScope cp) => Contract cp st -> Value st -> SomeContractAndStorage deriving stock instance Show SomeContractAndStorage data SomeStorage where SomeStorage :: forall st. StorageScope st => Value st -> SomeStorage deriving stock instance Show SomeStorage