-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# LANGUAGE EmptyDataDeriving #-} -- | Re-exports typed Value, CValue, some core types, some helpers and -- defines aliases for constructors of typed values. -- module Lorentz.Value ( M.Value , M.IsoValue (..) , M.WellTypedToT -- * Primitive types , Integer , Natural , MText , Bool (..) , ByteString , Address , EpAddress (..) , Mutez , Never , Timestamp , ChainId , KeyHash , PublicKey , Signature , Bls12381Fr , Bls12381G1 , Bls12381G2 , Set , Map , M.BigMapId (..) , M.BigMap , M.mkBigMap , M.Operation , Maybe (..) , List , ReadTicket (..) , ContractRef (..) , TAddress (..) , FutureContract (..) , M.Ticket (..) , Chest , ChestKey , OpenChest , M.EpName , pattern M.DefEpName , M.EntrypointCall , M.SomeEntrypointCall -- * Constructors , tz , toMutez , zeroMutez , oneMutez , mt , timestampFromSeconds , timestampFromUTCTime , timestampQuote -- * Conversions , M.coerceContractRef , callingAddress , callingDefAddress , ToAddress (..) , ToTAddress (..) , ToContractRef (..) , FromContractRef (..) , convertContractRef -- * Misc , Show , Default (..) , Label (..) , PrintAsValue (..) -- * Re-exports , module ReExports ) where import Data.Constraint ((\\)) import Data.Default (Default(..)) import Prelude hiding (Rational) import Fmt (Buildable(..)) import Lorentz.Address import Lorentz.Constraints.Scopes import Morley.AsRPC (HasRPCRepr(..)) import Morley.Michelson.Text import Morley.Michelson.Typed qualified as M import Morley.Michelson.Typed.Haskell.Compatibility as ReExports import Morley.Tezos.Core (ChainId, Mutez, Timestamp, oneMutez, timestampFromSeconds, timestampFromUTCTime, timestampQuote, toMutez, tz, zeroMutez) import Morley.Tezos.Crypto (Bls12381Fr, Bls12381G1, Bls12381G2, Chest, ChestKey, KeyHash, PublicKey, Signature) import Morley.Util.CustomGeneric as ReExports import Morley.Util.Label (Label(..)) import Lorentz.Annotation type List = [] data Never deriving stock (Generic, Show, Eq, Ord) deriving anyclass (M.IsoValue, NFData) instance Buildable Never where build = \case instance HasAnnotation Never where getAnnotation _ = M.starNotes instance HasRPCRepr Never where type AsRPC Never = Never instance M.TypeHasDoc Never where typeDocMdDescription = "An uninhabited type." -- | Value returned by @READ_TICKET@ instruction. data ReadTicket a = ReadTicket { rtTicketer :: Address , rtData :: a , rtAmount :: Natural } deriving stock (Show, Eq, Ord) customGeneric "ReadTicket" rightComb deriving anyclass instance M.IsoValue a => M.IsoValue (ReadTicket a) -- | Provides 'Buildable' instance that prints Lorentz value via Michelson's -- 'M.Value'. -- -- Result won't be very pretty, but this avoids requiring 'Show' or -- 'Buildable' instances. newtype PrintAsValue a = PrintAsValue a instance NiceUntypedValue a => Buildable (PrintAsValue a) where build (PrintAsValue a) = build (M.toVal a) \\ niceUntypedValueEvi @a data OpenChest = ChestContent ByteString | ChestOpenFailed Bool deriving stock (Generic, Show, Eq) deriving anyclass (M.IsoValue, HasAnnotation) instance M.TypeHasDoc OpenChest where typeDocMdDescription = "Result of opening a chest"