module Lorentz.Value
( Value
, IsoValue (..)
, IsoCValue (..)
, CValue (..)
, Integer
, Natural
, MText
, Bool (..)
, ByteString
, Address
, EpAddress (..)
, Mutez
, Timestamp
, ChainId
, KeyHash
, PublicKey
, Signature
, Set
, Map
, M.BigMap (..)
, M.Operation
, Maybe (..)
, List
, ContractRef (..)
, TAddress (..)
, FutureContract (..)
, M.EpName
, pattern M.DefEpName
, EntryPointCall
, SomeEntryPointCall
, toMutez
, mt
, timestampFromSeconds
, timestampFromUTCTime
, timestampQuote
, M.coerceContractRef
, callingTAddress
, callingDefTAddress
, ToAddress (..)
, ToTAddress (..)
, ToContractRef (..)
, FromContractRef (..)
, convertContractRef
, Default (..)
, Label (..)
) where
import Data.Default (Default(..))
import Data.Type.Bool (type (&&), Not)
import Data.Kind as Kind
import Data.Vinyl.Derived (Label(..))
import Lorentz.Constraints
import Michelson.Text
import Michelson.Typed
(ContractRef(..), EntryPointCall, IsoCValue(..), IsoValue(..), SomeEntryPointCall, Value)
import qualified Michelson.Typed as M
import Michelson.Typed.CValue (CValue(..))
import qualified Lorentz.EntryPoints.Core as Ep
import Michelson.Typed.EntryPoints (EpAddress(..))
import Tezos.Address (Address)
import Tezos.Core
(ChainId, Mutez, Timestamp, timestampFromSeconds, timestampFromUTCTime, timestampQuote, toMutez)
import Tezos.Crypto (KeyHash, PublicKey, Signature)
import Util.TypeLits
import Util.Type
type List = []
newtype TAddress p = TAddress { unTAddress :: Address }
deriving stock Generic
deriving anyclass IsoValue
callingTAddress
:: forall cp mname.
(NiceParameterFull cp)
=> TAddress cp
-> Ep.EntryPointRef mname
-> ContractRef (Ep.GetEntryPointArgCustom cp mname)
callingTAddress (TAddress addr) epRef =
withDict (niceParameterEvi @cp) $
case Ep.parameterEntryPointCallCustom @cp epRef of
epc@M.EntryPointCall{} -> ContractRef addr (M.SomeEpc epc)
callingDefTAddress
:: forall cp.
(NiceParameterFull cp)
=> TAddress cp
-> ContractRef (Ep.GetDefaultEntryPointArg cp)
callingDefTAddress taddr = callingTAddress taddr Ep.CallDefault
newtype FutureContract arg = FutureContract { unFutureContract :: ContractRef arg }
instance IsoValue (FutureContract arg) where
type ToT (FutureContract arg) = ToT EpAddress
toVal (FutureContract contract) = toVal $ M.contractRefToAddr contract
fromVal = error "Fetching 'FutureContract' back from Michelson is impossible"
class ToAddress a where
toAddress :: a -> Address
instance ToAddress Address where
toAddress = id
instance ToAddress EpAddress where
toAddress = eaAddress
instance ToAddress (TAddress cp) where
toAddress = unTAddress
instance ToAddress (FutureContract cp) where
toAddress = toAddress . unFutureContract
instance ToAddress (ContractRef cp) where
toAddress = crAddress
class ToTAddress (cp :: Kind.Type) (a :: Kind.Type) where
toTAddress :: a -> TAddress cp
instance ToTAddress cp Address where
toTAddress = TAddress
instance (cp ~ cp') => ToTAddress cp (TAddress cp') where
toTAddress = id
class ToContractRef (cp :: Kind.Type) (contract :: Kind.Type) where
toContractRef :: HasCallStack => contract -> ContractRef cp
instance (cp ~ cp') => ToContractRef cp (ContractRef cp') where
toContractRef = id
instance (NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') where
toContractRef = unFutureContract
instance ( FailWhen cond msg
, cond ~
( Ep.CanHaveEntryPoints cp &&
Not (Ep.ParameterEntryPointsDerivation cp == Ep.EpdNone)
)
, msg ~
( 'Text "Cannot apply `ToContractRef` to `TAddress`" ':$$:
'Text "Consider using call(Def)TAddress first`" ':$$:
'Text "(or if you know your parameter type is primitive," ':$$:
'Text " make sure typechecker also knows about that)" ':$$:
'Text "For parameter `" ':<>: 'ShowType cp ':<>: 'Text "`"
)
, cp ~ arg, NiceParameter arg
, NiceParameterFull cp, Ep.GetDefaultEntryPointArg cp ~ cp
) =>
ToContractRef arg (TAddress cp) where
toContractRef = callingDefTAddress
class FromContractRef (cp :: Kind.Type) (contract :: Kind.Type) where
fromContractRef :: ContractRef cp -> contract
instance (cp ~ cp') => FromContractRef cp (ContractRef cp') where
fromContractRef = id
instance (cp ~ cp') => FromContractRef cp (FutureContract cp') where
fromContractRef = FutureContract . fromContractRef
instance FromContractRef cp EpAddress where
fromContractRef = M.contractRefToAddr
instance FromContractRef cp Address where
fromContractRef = crAddress
convertContractRef
:: forall cp contract2 contract1.
(ToContractRef cp contract1, FromContractRef cp contract2)
=> contract1 -> contract2
convertContractRef = fromContractRef @cp . toContractRef