-- GeNeRaTeD fOr: ../SIMPLE-cbs/SIMPLE//SIMPLE-4-Declarations/SIMPLE-4-Declarations.cbs {-# LANGUAGE OverloadedStrings #-} module Funcons.SIMPLE.SIMPLE4Declarations.SIMPLE4Declarations where import Funcons.EDSL import Funcons.Operations hiding (Values,libFromList) entities = [] types = typeEnvFromList [] funcons = libFromList [("allocate-nested-vectors",StrictFuncon stepAllocate_nested_vectors)] allocate_nested_vectors_ fargs = FApp "allocate-nested-vectors" (fargs) stepAllocate_nested_vectors fargs = evalRules [rewrite1,rewrite2] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "N") (TName "nats")] env rewriteTermTo (TApp "allocate-initialised-variable" [TApp "vectors" [TName "variables"],TApp "vector" [TApp "left-to-right-repeat" [TApp "allocate-variable" [TName "values"],TFuncon (FValue (Nat 1)),TVar "N"]]]) env rewrite2 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "N") (TName "nats"),VPAnnotated (VPSeqVar "N+" PlusOp) (TSortSeq (TName "nats") PlusOp)] env rewriteTermTo (TApp "allocate-initialised-variable" [TApp "vectors" [TName "variables"],TApp "vector" [TApp "left-to-right-repeat" [TApp "allocate-nested-vectors" [TVar "N+"],TFuncon (FValue (Nat 1)),TVar "N"]]]) env