-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ -- | Duplication of Backend functions, but without input and output stack. module Indigo.Frontend.Language ( -- * Assignment and modifications new , setVar , setField , (+=) , (-=) , (*=) , (<<<=) , (>>>=) , (&&=) , (||=) , (^=) , (=:) -- * Storage Fields , getStorageField , setStorageField , updateStorageField -- * Conditional , if_ , when , unless , ifSome , ifNone , whenSome , whenNone , ifRight , ifLeft , whenRight , whenLeft , ifCons -- * Case , case_ , caseRec , entryCase , entryCaseRec , entryCaseSimple , (//->) , (#=) -- * Scope , scope , defFunction , defContract , defNamedPureLambda1 , defNamedLambda1 , defNamedLambda0 , defNamedEffLambda1 -- * Loop , while , whileLeft , forEach -- * Contract call , selfCalling , contractCalling -- * Documentation , doc , docGroup , docStorage , contractName , contractGeneral , contractGeneralDefault , finalizeParamCallingDoc -- * Short-handed doc item , anchor , description , example -- * Side-effects operations , transferTokens , setDelegate , createContract , createLorentzContract -- * Failures , failWith , assert , failCustom , failCustom_ , failUnexpected_ , assertCustom , assertCustom_ -- * Comments , comment , justComment , commentAroundFun , commentAroundStmt -- * Blocks , IndigoFunction , IndigoProcedure , IndigoEntrypoint -- * Helpers , liftIndigoState ) where import qualified Indigo.Backend as B import Indigo.Backend.Case hiding (caseRec, entryCaseRec) import Indigo.Backend.Lambda import Indigo.Backend.Scope import Indigo.Compilation (compileIndigoContract) import Indigo.Frontend.Program import Indigo.Frontend.Statement import Indigo.Internal hiding (SetField, return, (>>), (>>=)) import Indigo.Lorentz import Indigo.Prelude import Lorentz.Entrypoints.Helpers (RequireSumType) import qualified Lorentz.Instr as L import qualified Lorentz.Run as L import qualified Michelson.Typed as MT import qualified Michelson.Typed.Arith as M import Michelson.Typed.Haskell.Instr.Sum (CaseClauseParam(..), CtorField(..)) import Util.Markdown (toAnchor) import Util.TypeLits (AppendSymbol) import Util.TypeTuple.Class oneIndigoM :: StatementF IndigoM a -> IndigoM a oneIndigoM st = IndigoM (Instr st) liftIndigoState :: (forall inp. SomeIndigoState inp a) -> IndigoM a liftIndigoState code = IndigoM (Instr $ LiftIndigoState code) varModification :: (IsExpr ey y, IsObject x) => ([y, x] :-> '[x]) -> Var x -> ey -> IndigoM () varModification act v = oneIndigoM . VarModification act v . toExpr ---------------------------------------------------------------------------- -- Var creation and assignment ---------------------------------------------------------------------------- -- | Create a new variable with the result of the given expression as its initial value. new :: IsExpr ex x => ex -> IndigoM (Var x) new = oneIndigoM . NewVar . toExpr -- | Set the given variable to the result of the given expression. setVar :: (IsExpr ex x) => Var x -> ex -> IndigoM () setVar v = oneIndigoM . SetVar v . toExpr infixr 0 =: (=:) :: IsExpr ex x => Var x -> ex -> IndigoM () v =: e = setVar v e setField :: ( ex :~> ftype , IsObject dt , IsObject ftype , HasField dt fname ftype ) => Var dt -> Label fname -> ex -> IndigoM () setField v fName = oneIndigoM . SetField v fName . toExpr (+=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Add n m, ArithResHs M.Add n m ~ m ) => Var m -> ex1 -> IndigoM () (+=) = varModification L.add (-=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Sub n m, ArithResHs M.Sub n m ~ m ) => Var m -> ex1 -> IndigoM () (-=) = varModification L.sub (*=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Mul n m, ArithResHs M.Mul n m ~ m ) => Var m -> ex1 -> IndigoM () (*=) = varModification L.mul (||=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Or n m, ArithResHs M.Or n m ~ m ) => Var m -> ex1 -> IndigoM () (||=) = varModification L.or (&&=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.And n m, ArithResHs M.And n m ~ m ) => Var m -> ex1 -> IndigoM () (&&=) = varModification L.and (^=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Xor n m, ArithResHs M.Xor n m ~ m ) => Var m -> ex1 -> IndigoM () (^=) = varModification L.xor (<<<=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Lsl n m, ArithResHs M.Lsl n m ~ m ) => Var m -> ex1 -> IndigoM () (<<<=) = varModification L.lsl (>>>=) :: ( IsExpr ex1 n, IsObject m , ArithOpHs M.Lsr n m, ArithResHs M.Lsr n m ~ m ) => Var m -> ex1 -> IndigoM () (>>>=) = varModification L.lsr ---------------------------------------------------------------------------- -- Storage Fields ---------------------------------------------------------------------------- -- | Sets a storage field to a new value. setStorageField :: forall store name ftype ex. ( HasStorage store , ex :~> ftype , IsObject store , IsObject ftype , HasField store name ftype ) => Label name -> ex -> IndigoM () setStorageField field expr = setField (storageVar @store) field expr -- | Updates a storage field by using an updating 'IndigoM'. updateStorageField :: forall store ftype fname fex. ( HasStorage store , fex :~> ftype , HasField store fname ftype , IsObject store , IsObject ftype ) => Label fname -> (Var ftype -> IndigoM fex) -> IndigoM () updateStorageField field upd = scope $ do let storage = storageVar @store fieldVar <- new$ storage #! field expr <- upd fieldVar setField storage field expr -- | Get a field from the storage, returns a variable. -- -- Note that the storage type almost always needs to be specified. getStorageField :: forall store ftype fname . ( HasStorage store , HasField store fname ftype ) => Label fname -> IndigoM (Var ftype) getStorageField field = new$ storageVar @store #! field ---------------------------------------------------------------------------- -- Conditional ---------------------------------------------------------------------------- if_ :: forall a b ex . (IfConstraint a b, ex :~> Bool) => ex -> IndigoM a -> IndigoM b -> IndigoM (RetVars a) if_ ex tb fb = oneIndigoM $ If (toExpr ex) tb fb -- | Run the instruction when the condition is met, do nothing otherwise. when :: (exc :~> Bool) => exc -> IndigoM () -> IndigoM () when cond expr = if_ cond expr (return ()) -- | Reverse of 'when'. unless :: (exc :~> Bool) => exc -> IndigoM () -> IndigoM () unless cond expr = if_ cond (return ()) expr ifSome :: forall x a b ex . (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> (Var x -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a) ifSome ex tb fb = oneIndigoM $ IfSome (toExpr ex) tb fb ifNone :: forall x a b ex . (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> IndigoM b -> (Var x -> IndigoM a) -> IndigoM (RetVars a) ifNone ex fb tb = ifSome (toExpr ex) tb fb -- | Run the instruction when the given expression returns 'Just' a value, -- do nothing otherwise. whenSome :: forall x exa . ( KnownValue x , exa :~> Maybe x ) => exa -> (Var x -> IndigoM ()) -> IndigoM () whenSome c f = ifSome c f (return ()) -- | Run the instruction when the given expression returns 'Nothing', -- do nothing otherwise. whenNone :: forall x exa . ( KnownValue x , exa :~> Maybe x ) => exa -> IndigoM () -> IndigoM () whenNone c f = ifSome c (\_ -> return ()) f ifRight :: forall x y a b ex . ( KnownValue x , KnownValue y , ex :~> Either y x , IfConstraint a b ) => ex -> (Var x -> IndigoM a) -> (Var y -> IndigoM b) -> IndigoM (RetVars a) ifRight ex rb lb = oneIndigoM $ IfRight (toExpr ex) rb lb ifLeft :: forall x y a b ex . ( KnownValue x , KnownValue y , ex :~> Either y x , IfConstraint a b ) => ex -> (Var y -> IndigoM b) -> (Var x -> IndigoM a) -> IndigoM (RetVars a) ifLeft ex lb rb = ifRight ex rb lb whenRight :: forall x y ex . ( KnownValue x , KnownValue y , ex :~> Either y x ) => ex -> (Var x -> IndigoM ()) -> IndigoM () whenRight c f = ifRight c f (\_ -> return ()) whenLeft :: forall x y ex . ( KnownValue x , KnownValue y , ex :~> Either y x ) => ex -> (Var y -> IndigoM ()) -> IndigoM () whenLeft c f = ifRight c (\_ -> return ()) f ifCons :: forall x a b ex . (KnownValue x, ex :~> List x, IfConstraint a b) => ex -> (Var x -> Var (List x) -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a) ifCons ex tb fb = oneIndigoM $ IfCons (toExpr ex) tb fb ---------------------------------------------------------------------------- -- Case ---------------------------------------------------------------------------- -- | A case statement for indigo. See examples for a sample usage. caseRec :: forall dt guard ret clauses . ( CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses , guard :~> dt ) => guard -> clauses -> IndigoM (RetVars ret) caseRec g = oneIndigoM . Case (toExpr g) -- | 'caseRec' for tuples. case_ :: forall dt guard ret clauses. ( CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses , RecFromTuple clauses , guard :~> dt ) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) case_ g = caseRec (toExpr g) . recFromTuple @clauses -- | 'caseRec' for pattern-matching on parameter. entryCaseRec :: forall dt entrypointKind guard ret clauses . ( CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses , DocumentEntrypoints entrypointKind dt , guard :~> dt ) => Proxy entrypointKind -> guard -> clauses -> IndigoM (RetVars ret) entryCaseRec proxy g cls = oneIndigoM $ EntryCase proxy (toExpr g) cls -- | 'entryCaseRec' for tuples. entryCase :: forall dt entrypointKind guard ret clauses . ( CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses , RecFromTuple clauses , DocumentEntrypoints entrypointKind dt , guard :~> dt ) => Proxy entrypointKind -> guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) entryCase proxy g = entryCaseRec proxy g . recFromTuple @clauses entryCaseSimple :: forall cp guard ret clauses . ( CaseCommonF (IndigoMCaseClauseL IndigoM) cp ret clauses , RecFromTuple clauses , DocumentEntrypoints PlainEntrypointsKind cp , NiceParameterFull cp , RequireFlatParamEps cp , guard :~> cp ) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) entryCaseSimple g = oneIndigoM . EntryCaseSimple (toExpr g) . recFromTuple @clauses {-# DEPRECATED (//->) "use '#=' instead" #-} -- | An alias for '#=' kept only for backward compatibility. (//->) :: ( CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) , ScopeCodeGen retBr , ret ~ RetExprs retBr , RetOutStack ret ~ RetOutStack retBr , KnownValue x , name ~ (AppendSymbol "c" ctor) ) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x)) (//->) cName b = OneFieldIndigoMCaseClauseL cName b infixr 0 //-> -- | Use this instead of '/->'. -- -- This operator is like '/->' but wraps a body into 'IndigoAnyOut', -- which is needed for two reasons: to allow having any output stack -- and to allow returning not exactly the same values. -- -- It has the added benefit of not being an arrow, so in case the body of the -- clause is a lambda there won't be several. (#=) :: ( CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) , ScopeCodeGen retBr , ret ~ RetExprs retBr , RetOutStack ret ~ RetOutStack retBr , KnownValue x , name ~ (AppendSymbol "c" ctor) ) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x)) (#=) cName b = OneFieldIndigoMCaseClauseL cName b infixr 0 #= ---------------------------------------------------------------------------- -- Scope & Functions ---------------------------------------------------------------------------- -- | Utility type for an 'IndigoM' that adds one element to the stack and returns -- a variable pointing at it. type IndigoFunction ret = IndigoM (RetVars ret) -- | Utility type for an 'IndigoM' that does not modify the stack (only the -- values in it) and returns nothing. type IndigoProcedure = IndigoM () type IndigoEntrypoint param = param -> IndigoProcedure scope :: forall a . ScopeCodeGen a => IndigoM a -> IndigoFunction a scope = oneIndigoM . Scope -- | Alias for 'scope' we use in the tutorial. defFunction :: forall a . ScopeCodeGen a => IndigoM a -> IndigoFunction a defFunction = scope -- | A more specific version of 'defFunction' meant to more easily create -- 'IndigoContract's. -- -- Used in the tutorial. The 'HasSideEffects' constraint is -- specified to avoid the warning for redundant constraints. defContract :: (HasSideEffects => IndigoM ()) -> (HasSideEffects => IndigoProcedure) defContract = scope -- | Family of @defNamed*LambdaN@ functions put an Indigo computation -- on the stack to later call it avoiding code duplication. -- @defNamed*LambdaN@ takes a computation with N arguments. -- This family of functions add some overhead to contract byte size -- for every call of the function, -- therefore, DON'T use @defNamed*LambdaN@ if: -- * Your computation is pretty small. -- It would be cheaper just to inline it, so use 'defFunction'. -- * Your computation is called only once, in this case also use 'defFunction'. -- -- Also, pay attention that @defNamed*LambdaN@ accepts a string that is -- a name of the passed computation. Be careful and make sure that all -- declared computations have different names. -- Later the name will be removed. -- -- Pay attention, that lambda argument will be evaluated -- to variable before lambda calling. -- -- TODO Approach with lambda names has critical pitfall: -- in case if a function takes @Label name@, lambda body -- won't be regenerated for every different label. -- So be carefully, this will be fixed in a following issue. defNamedEffLambda1 :: forall st argExpr res . ( ToExpr argExpr , Typeable res , ExecuteLambdaEff1C st (ExprType argExpr) res , CreateLambdaEff1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> (argExpr -> IndigoM (RetVars res)) defNamedEffLambda1 lName body = \ex -> oneIndigoM $ LambdaEff1Call (Proxy @st) lName body (toExpr ex) -- | Like defNamedEffLambda1 but doesn't make side effects. defNamedLambda1 :: forall st argExpr res . ( ToExpr argExpr , Typeable res , ExecuteLambda1C st (ExprType argExpr) res , CreateLambda1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> (argExpr -> IndigoM (RetVars res)) defNamedLambda1 lName body = \ex -> oneIndigoM $ Lambda1Call (Proxy @st) lName body (toExpr ex) -- | Like defNamedLambda1 but doesn't take an argument. defNamedLambda0 :: forall st res . ( Typeable res , ExecuteLambda1C st () res , CreateLambda1C st () res) => String -> IndigoM res -> IndigoM (RetVars res) defNamedLambda0 lName body = oneIndigoM $ Lambda1Call (Proxy @st) lName (\(_ :: Var ()) -> body) (C ()) -- | Like defNamedEffLambda1 but doesn't modify storage and doesn't make side effects. defNamedPureLambda1 :: forall argExpr res . ( ToExpr argExpr , Typeable res , ExecuteLambdaPure1C (ExprType argExpr) res , CreateLambdaPure1C (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> (argExpr -> IndigoM (RetVars res)) defNamedPureLambda1 lName body = \ex -> oneIndigoM $ LambdaPure1Call lName body (toExpr ex) ---------------------------------------------------------------------------- -- Loop ---------------------------------------------------------------------------- -- | While statement. while :: forall ex . ex :~> Bool => ex -> IndigoM () -> IndigoM () while e body = oneIndigoM $ While (toExpr e) body whileLeft :: forall x y ex . ( ex :~> Either y x , KnownValue y , KnownValue x ) => ex -> (Var y -> IndigoM ()) -> IndigoM (Var x) whileLeft e body = oneIndigoM $ WhileLeft (toExpr e) body -- | For statements to iterate over a container. forEach :: forall a e . (IterOpHs a, KnownValue (IterOpElHs a), e :~> a) => e -> (Var (IterOpElHs a) -> IndigoM ()) -> IndigoM () forEach container body = oneIndigoM $ ForEach (toExpr container) body ---------------------------------------------------------------------------- -- Documentation ---------------------------------------------------------------------------- -- | Put a document item. doc :: DocItem di => di -> IndigoM () doc di = liftIndigoState $ toSIS $ B.doc di -- | Group documentation built in the given piece of code -- into a block dedicated to one thing, e.g. to one entrypoint. docGroup :: DocGrouping -> IndigoM () -> IndigoM () docGroup = oneIndigoM ... DocGroup -- | Insert documentation of the contract's storage type. The type -- should be passed using type applications. docStorage :: forall storage. TypeHasDoc storage => IndigoM () docStorage = liftIndigoState $ toSIS $ B.docStorage @storage -- | Give a name to the given contract. Apply it to the whole contract code. contractName :: Text -> IndigoM () -> IndigoM () contractName = oneIndigoM ... ContractName -- | Attach general info to the given contract. contractGeneral :: IndigoM () -> IndigoM () contractGeneral = oneIndigoM . ContractGeneral -- | Attach default general info to the contract documentation. contractGeneralDefault :: IndigoM () contractGeneralDefault = liftIndigoState $ toSIS $ B.contractGeneralDefault -- | Indigo version for the homonym Lorentz function. finalizeParamCallingDoc :: forall param x. ( ToExpr param , NiceParameterFull (ExprType param) , RequireSumType (ExprType param) , HasCallStack ) => (Var (ExprType param) -> IndigoM x) -> param -> IndigoM x finalizeParamCallingDoc i = oneIndigoM . FinalizeParamCallingDoc i . toExpr -- | Put a 'DDescription' doc item. description :: Markdown -> IndigoM () description = doc . DDescription -- | Put a 'DAnchor' doc item. anchor :: Text -> IndigoM () anchor = doc . DAnchor . toAnchor -- | Put a 'DEntrypointExample' doc item. example :: forall a. NiceParameter a => a -> IndigoM () example = doc . mkDEntrypointExample ---------------------------------------------------------------------------- -- Contract call ---------------------------------------------------------------------------- selfCalling :: forall p mname. ( NiceParameterFull p , KnownValue (GetEntrypointArgCustom p mname) ) => EntrypointRef mname -> IndigoM (Var (ContractRef (GetEntrypointArgCustom p mname))) selfCalling ep = liftIndigoState $ toSIS $ B.selfCalling @p ep contractCalling :: forall cp epRef epArg addr exAddr. ( HasEntrypointArg cp epRef epArg , ToTAddress cp addr , ToT addr ~ ToT Address , exAddr :~> addr , KnownValue epArg ) => epRef -> exAddr -> IndigoM (Var (Maybe (ContractRef epArg))) contractCalling epRef = oneIndigoM . ContractCalling (Proxy @cp) epRef . toExpr ---------------------------------------------------------------------------- -- Side-effects operations ---------------------------------------------------------------------------- transferTokens :: (IsExpr exp p, IsExpr exm Mutez, IsExpr exc (ContractRef p), NiceParameter p, HasSideEffects) => exp -> exm -> exc -> IndigoM () transferTokens ep em ec = oneIndigoM $ TransferTokens (toExpr ep) (toExpr em) (toExpr ec) setDelegate :: (HasSideEffects, IsExpr ex (Maybe KeyHash)) => ex -> IndigoM () setDelegate = oneIndigoM . SetDelegate . toExpr -- | Create contract using default compilation options for Lorentz compiler. -- -- See "Lorentz.Run". createContract :: ( IsObject st , IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st , NiceStorage st, NiceParameterFull param , HasSideEffects ) => (HasStorage st => Var param -> IndigoM ()) -> exk -> exm -> exs -> IndigoM (Var Address) createContract iCtr ek em es = oneIndigoM $ CreateContract (defaultContract $ compileIndigoContract iCtr) (toExpr ek) (toExpr em) (toExpr es) -- | Create contract from raw Lorentz 'L.Contract'. createLorentzContract :: ( IsObject st , IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st , NiceStorage st, NiceParameterFull param , HasSideEffects ) => L.Contract param st -> exk -> exm -> exs -> IndigoM (Var Address) createLorentzContract lCtr ek em es = oneIndigoM $ CreateContract lCtr (toExpr ek) (toExpr em) (toExpr es) ---------------------------------------------------------------------------- -- Error ---------------------------------------------------------------------------- assert :: forall x ex. ( IsError x , IsExpr ex Bool ) => x -> ex -> IndigoM () assert x = oneIndigoM . Assert x . toExpr failWith :: forall r a ex . IsExpr ex a => ex -> IndigoM r failWith = oneIndigoM . FailWith . toExpr failCustom :: forall r tag err ex. ( err ~ ErrorArg tag , CustomErrorHasDoc tag , NiceConstant err , ex :~> err ) => Label tag -> ex -> IndigoM r failCustom l = oneIndigoM . FailCustom l . toExpr failCustom_ :: forall r tag notVoidErrorMsg. ( RequireNoArgError tag notVoidErrorMsg , CustomErrorHasDoc tag ) => Label tag -> IndigoM r failCustom_ lab = liftIndigoState $ toSIS $ B.failCustom_ lab failUnexpected_ :: MText -> IndigoM r failUnexpected_ tx = liftIndigoState $ toSIS $ B.failUnexpected_ tx assertCustom :: forall tag err errEx ex . ( err ~ ErrorArg tag , CustomErrorHasDoc tag , NiceConstant err , IsExpr errEx err , IsExpr ex Bool ) => Label tag -> errEx -> ex -> IndigoM () assertCustom tag errEx e = if_ (toExpr e) (return ()) (failCustom tag errEx :: IndigoM ()) assertCustom_ :: forall tag notVoidErrorMsg ex. ( RequireNoArgError tag notVoidErrorMsg , CustomErrorHasDoc tag , IsExpr ex Bool ) => Label tag -> ex -> IndigoM () assertCustom_ tag e = if_ (toExpr e) (return ()) (failCustom_ tag :: IndigoM ()) ---------------------------------------------------------------------------- -- Comments ---------------------------------------------------------------------------- -- | Add a comment in a generated Michelson code justComment :: Text -> IndigoM () justComment = comment . MT.JustComment -- | Add a comment in a generated Michelson code comment :: MT.CommentType -> IndigoM () comment t = liftIndigoState $ toSIS (B.comment t) -- | Add a comment before and after the given Indigo function code. -- The first argument is the name of the function. commentAroundFun :: Text -> IndigoM a -> IndigoM a commentAroundFun fName body = comment (MT.FunctionStarts fName) >> body >>= \res -> res <$ comment (MT.FunctionEnds fName) -- | Add a comment before and after the given Indigo statement code. -- The first argument is the name of the statement. commentAroundStmt :: Text -> IndigoM a -> IndigoM a commentAroundStmt sName body = comment (MT.StatementStarts sName) >> body >>= \res -> res <$ comment (MT.StatementEnds sName)