-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Control flow/Abnormal/Throwing/finally.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.ControlFlow.Abnormal.Throwing.Finally where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("finally",NonStrictFuncon stepFinally)] -- | -- /finally(C,F)/ first executes /C/ . -- If /C/ terminates normally, then /F/ executes. -- If /C/ abruptly terminates with a thrown value /V/ , then /F/ executes, -- and then /V/ is rethrown. finally_ fargs = FApp "finally" (FTuple fargs) stepFinally fargs = evalRules [rewrite1] [step1,step2] where rewrite1 = do let env = emptyEnv env <- fsMatch fargs [PValue (PTuple []),PMetaVar "F"] env rewriteTermTo (TVar "F") env step1 = do let env = emptyEnv env <- lifted_fsMatch fargs [PMetaVar "C",PMetaVar "F"] env env <- receiveSignalPatt "thrown" (Nothing) (premise (TVar "C") (PMetaVar "C'") env) stepTermTo (TApp "finally" (TTuple [TVar "C'",TVar "F"])) env step2 = do let env = emptyEnv env <- lifted_fsMatch fargs [PMetaVar "C",PMetaVar "F"] env env <- receiveSignalPatt "thrown" (Just (VPAnnotated (VPMetaVar "V") (TName "values"))) (premise (TVar "C") (PWildCard) env) stepTermTo (TApp "sequential" (TTuple [TVar "F",TApp "throw" (TTuple [TVar "V"])])) env