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