-- GeNeRaTeD fOr: ../../CBS/Funcons/Values/Primitive values/Numbers/rationals.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Values.PrimitiveValues.Numbers.Rationals where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("negate",StrictFuncon stepNegate),("exponent-notation",StrictFuncon stepExponent_notation)] negate_ fargs = FApp "negate" (FTuple fargs) stepNegate fargs = evalRules [rewrite1] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "R") (TName "values")] env rewriteTermTo (TApp "subtract" (TTuple [TFuncon (FValue (Nat 0)),TVar "R"])) env exponent_notation_ fargs = FApp "exponent-notation" (FTuple fargs) stepExponent_notation fargs = evalRules [rewrite1] [] where rewrite1 = do let env = emptyEnv env <- vsMatch fargs [VPAnnotated (VPMetaVar "R") (TName "values"),VPAnnotated (VPMetaVar "I") (TName "values")] env rewriteTermTo (TApp "multiply" (TTuple [TVar "R",TApp "power" (TTuple [TFuncon (FValue (Nat 10)),TVar "I"])])) env