-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Control flow/Abnormal/Continuations/shift.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.ControlFlow.Abnormal.Continuations.Shift where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("shift",StrictFuncon stepShift)] -- | -- /shift(F)/ emits a /control-signal/ that, when handled by an enclosing -- /reset/ , will cause /F/ to the current continuation of /shift(F)/ , -- Unlike /control/ , any application of the captured continuation delimits -- any control operators in its body. shift_ fargs = FApp "shift" (FTuple fargs) stepShift fargs = evalRules [] [step1] where step1 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPAnnotated (VPMetaVar "F") (TName "values")] env env <- premise (TName "fresh-binder") (PMetaVar "K") env stepTermTo (TApp "control" (TTuple [TApp "binding-lambda" (TTuple [TVar "K",TApp "apply" (TTuple [TVar "F",TApp "lambda" (TTuple [TApp "reset" (TTuple [TApp "apply" (TTuple [TApp "bound" (TTuple [TVar "K"]),TName "given"])])])])])])) env