-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Data flow/Storing/Simple variables/allocate-variable.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.DataFlow.Storing.SimpleVariables.AllocateVariable where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("allocate-variable",StrictFuncon stepAllocate_variable)] -- | -- /allocate-variable(T)/ computes an (uninitialised) simple variable for storing -- values of type /T/ . allocate_variable_ fargs = FApp "allocate-variable" (FTuple fargs) stepAllocate_variable fargs = evalRules [] [step1] where step1 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPAnnotated (VPMetaVar "T") (TName "types")] env env <- getMutPatt "store" (VPMetaVar "Sigma") env putMutTerm "store" (TTuple [TVar "Sigma"]) env env <- premise (TName "fresh-atom") (PMetaVar "K") env env <- getMutPatt "store" (VPMetaVar "Sigma'") env env <- lifted_sideCondition (SCPatternMatch (TApp "simple-variable" (TTuple [TVar "K",TVar "T"])) (VPMetaVar "Var")) env putMutTerm "store" (TTuple [TApp "map-unite" (TTuple [TVar "Sigma'",TMap [TTuple [TVar "Var",TName "uninitialised"]]])]) env stepTermTo (TVar "Var") env