-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ -- | This module contains the high-level compilation of Indigo to Lorentz, -- including plain Indigo code, as well as Indigo contracts. module Indigo.Compilation ( compileIndigo , compileIndigoContract ) where import qualified Data.Map as M import Indigo.Compilation.Field import Indigo.Compilation.Lambda import Indigo.Compilation.Params import Indigo.Compilation.Sequential import Indigo.Frontend.Program (IndigoContract) import Indigo.Internal hiding (SetField, (>>)) import Indigo.Lorentz import Indigo.Prelude import qualified Lorentz.Instr as L import qualified Lorentz.Macro as L -- | Compile Indigo code to Lorentz. -- -- Note: it is necessary to specify the number of parameters (using the first -- type variable) of the Indigo function. Also, these should be on the top of -- the input stack in inverse order (see 'IndigoWithParams'). compileIndigoImpl :: forall n inp a. (AreIndigoParams n inp, KnownValue a, Default (StackVars inp)) => IndigoWithParams n inp a -> (StackVars inp -> (Block, RefId) -> (inp :-> inp)) -> inp :-> inp compileIndigoImpl paramCode runner = runner initMd optimized where (code, initMd, nextRef) = fromIndigoWithParams @n @a paramCode optimized = indigoMtoSequential nextRef code & compileLambdas & optimizeFields -- | Specialiasation of 'compileIndigoImpl' without var decompositions. compileIndigo :: forall n inp a. (AreIndigoParams n inp, KnownValue a, Default (StackVars inp)) => IndigoWithParams n inp a -> inp :-> inp compileIndigo paramCode = compileIndigoImpl @n @inp @a paramCode (\stk block -> sequentialToLorentz (MetaData stk mempty) block) -- | Compile Indigo code to Lorentz contract. -- Drop elements from the stack to return only @[Operation]@ and @storage@. compileIndigoContract :: forall param st . ( KnownValue param , IsObject st ) => IndigoContract param st -> ContractCode param st compileIndigoContract code = prepare $ compileIndigoImpl @3 @'[param, st, Ops] (contractToIndigoWithParams code) $ \(parRef :& storageRef :& opsStack) (block, nextRef) -> let stRef = case storageRef of NoRef -> error "Storage variable hasn't been assigned" Ref r -> r in -- during code Indigo code compilation the stack will look like: -- [var_10, var_9, ... , var_3, param_var_2, storage_field_11, storage_field_12, ..., storage_field_20, ops_var_0] -- var_1 will represent storage and passed to DecomposedObjects let (storageObj, nextRef', someGen) = deepDecomposeCompose nextRef (NoRef :& opsStack) in case someGen of SomeGenCode (GenCode decompStk decompose composeBack) -> let md = MetaData (parRef :& decompStk) $ M.singleton stRef (SomeObject storageObj) indigoCode = sequentialToLorentz md (block, nextRef') in L.dip decompose # -- decompose storage indigoCode # -- run indigo code L.dip composeBack where prepare :: ('[param, st, Ops] :-> '[param, st, Ops]) -> ('[(param, st)] :-> '[(Ops, st)]) prepare cd = L.nil # L.swap # L.unpair # cd # L.drop # -- drop param L.swap # L.pair