-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Data flow/Linking/allocate-initialised-link.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.DataFlow.Linking.AllocateInitialisedLink where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("allocate-initialised-link",StrictFuncon stepAllocate_initialised_link)] -- | -- /allocate-initialised-link(T,V)/ computes a link to values of type /T/ , -- and sets its value to /V/ . -- This /fail/ s if the type of /V/ is not a subtype of /T/ . allocate_initialised_link_ fargs = FApp "allocate-initialised-link" (FTuple fargs) stepAllocate_initialised_link fargs = evalRules [rewrite1] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "T") (TName "values"),VPAnnotated (VPMetaVar "V") (TName "values")] env rewriteTermTo (TApp "give" (TTuple [TApp "allocate-link" (TTuple [TVar "T"]),TApp "sequential" (TTuple [TApp "set-link" (TTuple [TName "given",TVar "V"]),TName "given"])])) env