-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ {-# LANGUAGE EmptyDataDeriving #-} -- | Re-exports typed Value, CValue, some core types, some helpers and -- defines aliases for constructors of typed values. -- module Lorentz.Value ( Value , IsoValue (..) , WellTypedIsoValue -- * Primitive types , Integer , Natural , MText , Bool (..) , ByteString , Address , EpAddress (..) , Mutez , Never , Timestamp , ChainId , KeyHash , PublicKey , Signature , Bls12381Fr , Bls12381G1 , Bls12381G2 , Set , Map , M.BigMap (..) , M.Operation , Maybe (..) , List , ContractRef (..) , TAddress (..) , FutureContract (..) , M.EpName , pattern M.DefEpName , EntrypointCall , SomeEntrypointCall -- * Constructors , toMutez , zeroMutez , oneMutez , mt , timestampFromSeconds , timestampFromUTCTime , timestampQuote -- * Conversions , M.coerceContractRef , callingTAddress , callingDefTAddress , ToAddress (..) , ToTAddress (..) , ToContractRef (..) , FromContractRef (..) , convertContractRef -- * Misc , Show , Default (..) , Label (..) , PrintAsValue (..) -- * Re-exports , module ReExports ) where import Data.Constraint ((\\)) import Data.Default (Default(..)) import Fmt (Buildable(..)) import Lorentz.Address import Lorentz.Constraints.Scopes import Michelson.Text import Michelson.Typed (EntrypointCall, IsoValue(..), SomeEntrypointCall, Value, WellTypedIsoValue) import qualified Michelson.Typed as M import Michelson.Typed.Haskell.Compatibility as ReExports import Tezos.Core (ChainId, Mutez, Timestamp, oneMutez, timestampFromSeconds, timestampFromUTCTime, timestampQuote, toMutez, zeroMutez) import Tezos.Crypto (Bls12381Fr, Bls12381G1, Bls12381G2, KeyHash, PublicKey, Signature) import Util.CustomGeneric as ReExports import Util.Label (Label(..)) import Lorentz.Annotation type List = [] data Never deriving stock (Generic, Show, Eq, Ord) deriving anyclass (IsoValue, NFData) instance Buildable Never where build = \case instance HasAnnotation Never where getAnnotation _ = M.starNotes instance M.TypeHasDoc Never where typeDocMdDescription = "An uninhabited type." -- | Provides 'Buildable' instance that prints Lorentz value via Michelson's -- 'Value'. -- -- Result won't be very pretty, but this avoids requiring 'Show' or -- 'Buildable' instances. newtype PrintAsValue a = PrintAsValue a instance NicePrintedValue a => Buildable (PrintAsValue a) where build (PrintAsValue a) = build (toVal a) \\ nicePrintedValueEvi @a