-- GeNeRaTeD fOr: ../../CBS/Funcons/Abstractions/Closures/close.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Abstractions.Closures.Close where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("close",StrictFuncon stepClose)] -- | -- /close(_)/ closes a thunked computation with respect to the -- current environment. close_ fargs = FApp "close" (FTuple fargs) stepClose fargs = evalRules [] [step1] where step1 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPAnnotated (VPMetaVar "F") (TApp "thunks" (TTuple [TSortComputes (TName "values")]))] env env <- getInhPatt "environment" (VPMetaVar "Rho") env stepTermTo (TApp "thunk" (TTuple [TApp "closure" (TTuple [TApp "force" (TTuple [TVar "F"]),TVar "Rho"])])) env