-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Data flow/Storing/Simple variables/assigned.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.DataFlow.Storing.SimpleVariables.Assigned where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("assigned",StrictFuncon stepAssigned)] -- | -- /assigned(Var)/ gives the value currently assigned to the variable /Var/ . -- If this value is /uninitialised/ , then computation /fail/ s. assigned_ fargs = FApp "assigned" (FTuple fargs) stepAssigned fargs = evalRules [] [step1,step2,step3] where step1 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPMetaVar "Var"] env env <- getMutPatt "store" (VPMetaVar "Sigma") env env <- lifted_sideCondition (SCPatternMatch (TApp "lookup" (TTuple [TVar "Var",TVar "Sigma"])) (VPMetaVar "V")) env env <- lifted_sideCondition (SCNotInSort (TVar "V") (TName "uninitialised-values")) env putMutTerm "store" (TTuple [TVar "Sigma"]) env stepTermTo (TVar "V") env step2 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPMetaVar "Var"] env env <- getMutPatt "store" (VPMetaVar "Sigma") env env <- lifted_sideCondition (SCIsInSort (TApp "lookup" (TTuple [TVar "Var",TVar "Sigma"])) (TName "uninitialised-values")) env putMutTerm "store" (TTuple [TVar "Sigma"]) env stepTo (FName "fail") step3 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPMetaVar "Var"] env env <- getMutPatt "store" (VPMetaVar "Sigma") env env <- lifted_sideCondition (SCEquality (TApp "is-in-set" (TTuple [TVar "Var",TApp "domain" (TTuple [TVar "Sigma"])])) (TName "false")) env putMutTerm "store" (TTuple [TVar "Sigma"]) env stepTo (FName "fail")