-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ -- | Standard library for Indigo. -- -- As opposed to Expr and Language modules, this module contains quite -- standard things that are not present in vanilla Michelson and are -- not typically found in imperative high level languages. module Indigo.Lib ( -- * Views and Voids view_ , void_ , project , projectVoid -- * Others , subGt0 ) where import Indigo.Compilation import Indigo.Frontend import Indigo.Internal.Expr import Indigo.Lorentz import Indigo.Prelude import Indigo.Rebinded ---------------------------------------------------------------------------- -- Views and Voids ---------------------------------------------------------------------------- -- | Indigo version of the @view@ macro. It takes a function from view -- argument to view result and a 'View' structure that typically comes -- from a top-level @case@. view_ :: forall arg r viewExpr exr. ( KnownValue arg , NiceParameter r , viewExpr :~> View arg r , exr :~> r , HasSideEffects ) => (Expr arg -> IndigoM exr) -> viewExpr -> IndigoM () view_ f v = do r <- f (v #! #viewParam) transferTokens r amount (v #! #viewCallbackTo) -- | Flipped version of 'view_' that is present due to the common -- appearance of @flip view parameter $ instr@ construction. -- -- Semantically we "project" the given parameter inside the body -- of the 'View' construction. project :: forall arg r viewExpr exr. ( KnownValue arg , NiceParameter r , viewExpr :~> View arg r , exr :~> r , HasSideEffects ) => viewExpr -> (Expr arg -> IndigoM exr) -> IndigoM () project = flip view_ -- | Indigo version of the @void@ macro. void_ :: forall a b voidExpr exb. ( KnownValue a , IsError (VoidResult b) , NiceConstant b , voidExpr :~> Void_ a b , exb :~> b ) => (Expr a -> IndigoM exb) -> voidExpr -> IndigoM () void_ f v = do doc (DThrows (Proxy @(VoidResult b))) r <- f (v #! #voidParam) failWith $ pair voidResultTag (Exec r (v #! #voidResProxy)) -- | Flipped version of 'void_' that is present due to the common -- appearance of @flip void_ parameter $ instr@ construction. projectVoid :: forall a b voidExpr exb. ( KnownValue a , IsError (VoidResult b) , NiceConstant b , voidExpr :~> Void_ a b , exb :~> b ) => voidExpr -> (Expr a -> IndigoM exb) -> IndigoM () projectVoid = flip void_ ---------------------------------------------------------------------------- -- Others ---------------------------------------------------------------------------- -- | If the first value is greater than the second one, it returns their -- difference. If the values are equal, it returns 'Nothing'. Otherwise it -- fails using the supplied function. subGt0 ::(ex1 :~> Natural, ex2 :~> Natural) => ex1 -> ex2 -> IndigoM () -> IndigoFunction (Maybe Natural) subGt0 minuend subtrahend onNegative = do let diff :: Expr Integer diff = minuend - subtrahend zero :: Expr Integer zero = C $ 0 int when (diff < zero) onNegative resVar <- new$ Nothing if diff == zero then setVar resVar $ C Nothing else setVar resVar $ isNat diff return resVar