-- GeNeRaTeD fOr: ../../CBS/Funcons/Abstractions/Functions/compose.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Abstractions.Functions.Compose where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("compose",StrictFuncon stepCompose)] -- | -- /compose(G,F)/ composes two functions /G/ and /F/ by -- giving the result of /F/ as the argument to /G/ . compose_ fargs = FApp "compose" (FTuple fargs) stepCompose fargs = evalRules [rewrite1] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "G") (TName "values"),VPAnnotated (VPMetaVar "F") (TName "values")] env rewriteTermTo (TApp "thunk" (TTuple [TApp "apply" (TTuple [TVar "G",TApp "apply" (TTuple [TVar "F",TName "given"])])])) env