-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Data flow/Linking/allocate-link.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.DataFlow.Linking.AllocateLink where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("allocate-link",StrictFuncon stepAllocate_link)] -- | -- /allocate-link(T)/ computes a link to values of type /T/ . allocate_link_ fargs = FApp "allocate-link" (FTuple fargs) stepAllocate_link fargs = evalRules [] [step1] where step1 = do let env = emptyEnv env <- lifted_vsMatch fargs [VPAnnotated (VPMetaVar "T") (TName "types")] env env <- getMutPatt "link-store" (VPMetaVar "Sigma") env putMutTerm "link-store" (TTuple [TVar "Sigma"]) env env <- premise (TName "fresh-atom") (PMetaVar "K") env env <- getMutPatt "link-store" (VPMetaVar "Sigma'") env env <- lifted_sideCondition (SCPatternMatch (TApp "simple-link" (TTuple [TVar "K",TVar "T"])) (VPMetaVar "L")) env putMutTerm "link-store" (TTuple [TApp "map-unite" (TTuple [TVar "Sigma'",TMap [TTuple [TVar "L",TName "uninitialised"]]])]) env stepTermTo (TVar "L") env