-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ module Indigo.Compilation.Params ( IndigoWithParams , AreIndigoParams , fromIndigoWithParams , contractToIndigoWithParams ) where import Data.Reflection (give) import Data.Singletons (Sing, SingI(..)) import Indigo.Backend.Prelude import Indigo.Frontend.Program (IndigoM, IndigoContract) import Indigo.Internal.Var import Indigo.Lorentz import Util.Peano -- | Type of a function with @n@ 'Var' arguments and @IndigoM a@ result. -- -- Note that the arguments are the first @n@ elements of the @inp@ stack in -- inverse order, for example: -- @IndigoWithParams 2 [a, b, c] x@ is the same as: -- @Var b -> Var a -> IndigoM x@ type IndigoWithParams n inp a = IndigoWithPeanoParams (ToPeano n) inp a -- | Typeable and stack size constraints for the parameters of an 'IndigoWithParams' -- and for converting to a 'Peano' type AreIndigoParams n stk = ( AreIndigoPeanoParams (ToPeano n) stk , SingI (ToPeano n) ) -- | 'Peano' equivalent of 'IndigoWithParams' type family IndigoWithPeanoParams n inp a where IndigoWithPeanoParams 'Z _ a = IndigoM a IndigoWithPeanoParams ('S n) inp a = Var (At n inp) -> IndigoWithPeanoParams n inp a -- | Typeable and stack size constraints for the parameters of an 'IndigoWithPeanoParams'. type family AreIndigoPeanoParams n stk :: Constraint where AreIndigoPeanoParams 'Z _ = (() :: Constraint) AreIndigoPeanoParams ('S n) stk = (KnownValue (At n stk), RequireLongerThan stk n, AreIndigoPeanoParams n stk) -- | Converts an 'IndigoWithParams' to its form without input 'Var's, alongside -- the 'StackVars' to use it with and the first available (unassingned) 'RefId'. fromIndigoWithParams :: forall n a inp. (AreIndigoParams n inp, KnownValue a, Default (StackVars inp)) => IndigoWithParams n inp a -> (IndigoM a, StackVars inp, RefId) fromIndigoWithParams code = fromIndigoWithPeanoParams minBound def code (sing @(ToPeano n)) -- | 'Peano' version of 'fromIndigoWithParams' fromIndigoWithPeanoParams :: forall inp n a. (AreIndigoPeanoParams n inp, KnownValue a) => RefId -> StackVars inp -> IndigoWithPeanoParams n inp a -> Sing n -> (IndigoM a, StackVars inp, RefId) fromIndigoWithPeanoParams ref md code = \case SZ -> (code, md, ref) SS n -> let var = Var ref in fromIndigoWithPeanoParams @inp (ref + 1) (assignVarAt var md n) (code var) n -- | Converts an 'IndigoContract' to the equivalent 'IndigoM' with the storage, -- parameter and ops list as arguments. contractToIndigoWithParams :: forall param st . KnownValue st => IndigoContract param st -> IndigoWithParams 3 '[param, st, Ops] () contractToIndigoWithParams code = \varOps varSt varParam -> (give varOps $ give varSt code) varParam