GOTO

REDUC
E

INDEX

GOTO _ _ _ _ _ _ _ _ _ _ _ _ command

Inside a begin...end block, goto, or preferably, go to, transfers flow of control to a labeled statement.

syntax:

go to<labeled_statement> or goto <labeled_statement >

<labeled_statement> is of the form <label> :<statement >

examples:


     procedure dumb(a);
        begin scalar q;
           go to lab;
           q := df(a**2 - sin(a),a);
           write q;
      lab: return a
        end;
 

  DUMB 



dumb(17); 

  17

go tocan only be used inside a begin...end block, and inside the block only statements at the top level can be labeled, not ones inside <<...>>, while...do, etc.

GREATERP

REDUC
E

INDEX

GREATERP _ _ _ _ _ _ _ _ _ _ _ _ operator

The greaterp logical operator returns true if its first argument is strictly greater than its second argument. As an infix operator it is identical with >.

syntax:

greaterp(<expression>,<expression>) or <expression> greaterp <expression>

<expression> can be any valid REDUCE expression that evaluates to a number.

examples:



a := 20; 

  A := 20 


if greaterp(a,25) then write "big" else write "small";
			 


  small 


if a greaterp 20 then write "big" else write "small";
			 


  small 


if (a greaterp 18) then write "big" else write "small";
			 


  big

Logical operators can only be used in conditional statements such as

if...then...else or repeat... while.

IF

REDUC
E

INDEX

IF _ _ _ _ _ _ _ _ _ _ _ _ command

The if command is a conditional statement that executes a statement if a condition is true, and optionally another statement if it is not.

syntax:

if<condition> then <statement> _ _ _ option(else <statement>)

<condition> must be a logical or comparison operator that evaluates to a boolean value. <statement> must be a single REDUCE statement or a group (<<...>>) or block (begin...end) stateme nt.

examples:


if x = 5 then a := b+c else a := d+f;
			 


  D + F 


x := 9; 

  X := 9 


if numberp x and x<20 then y := sqrt(x) else write "illegal";
			 


  3  


clear x; 

if numberp x and x<20 then y := sqrt(x) else write "illegal";
			 


  illegal 


x := 12; 

  X := 12 


a := if x < 5 then 100 else 150;
			 


  A := 150 


b := u**(if x < 10 then 2);
			 

  B := 1 


bb := u**(if x > 10 then 2);
			 

         2
  BB := U

An if statement may be used inside an assignment statemen t and sets its value depending on the conditions, or used anywhere else an expression would be valid, as shown in the last example. If there is no else clause, the value is 0 if a number is expected, and nothing otherwise.

The else clause may be left out if no action is to be taken if the condition is false.

The condition may be a compound conditional statement using and or or. If a non-conditional statement, such as a constant, is used by accident, it is assumed to have value true.

Be sure to use group or block statements after then or else.

The if operator is right associative. The following constructions are examples:

_ _ _ (1)

syntax:

if<condition> then if <condition> the n <action> else <action>

which is equivalent to

syntax:

if<condition> then (if <condition> then <action> else <action>);

_ _ _ (2)

syntax:

if<condition> then <action> else if <condition> then <action> else <action>

which is equivalent to

syntax:

if<condition> then <action> else

(if <condition> then <action> else <action>).

LIST

REDUC
E

INDEX

LIST _ _ _ _ _ _ _ _ _ _ _ _ operator

The list operator constructs a list from its arguments.

syntax:

list(<item> {,<item>}*) or list() to construct an empty list.

<item> can be any REDUCE scalar expression, including another list. Left and right curly brackets can also be used instead of the operator list to construct a list.

examples:


liss := list(c,b,c,{xx,yy},3x**2+7x+3,df(sin(2*x),x));
	 


                            2
  LISS := {C,B,C,{XX,YY},3*X  + 7*X + 3,2*COS(2*X)} 


length liss; 

  6 


liss := {c,b,c,{xx,yy},3x**2+7x+3,df(sin(2*x),x)};
	 


                            2
  LISS := {C,B,C,{XX,YY},3*X  + 7*X + 3,2*COS(2*X)} 


emptylis := list(); 

  EMPTYLIS := {} 


a . emptylis; 

  {A}

Lists are ordered, hierarchical structures. The elements stay wher e you put them, and only change position in the list if you specifically change them. Lists can have nested sublists to any (reasonable) level. The part operator can be used to access elements anywhere within a list hierarchy. The length operator counts the number of top-level elements of its list argument; elements that are themselves lists still only count as one element.

OR

REDUC
E

INDEX

OR _ _ _ _ _ _ _ _ _ _ _ _ operator

The or binary logical operator returns true if either one or both of its arguments is true.

syntax:

<logical expression> or <logical expression>

<logical expression> must evaluate to true or nil.

examples:


a := 10; 

  A := 10 


if a<0 or a>140 then write "not a valid human age" else
   write "age = ",a;
 



  age = 10 


a := 200; 

  A := 200 


if a < 0 or a > 140 then write "not a valid human age";
			 


  not a valid human age

The or operator is left associative: x or y or z is equivalent to (x or y) or z.

Logical operators can only be used in conditional expressions, such as

if...then...else and while...do. or evaluates its arguments in order and quits, returning true, on finding the first true statement.

PROCEDURE

REDUC
E

INDEX

PROCEDURE _ _ _ _ _ _ _ _ _ _ _ _ command

The procedure command allows you to define a mathematical operation as a function with arguments.

syntax:

_ _ _ <option> procedure <identifier> (<arg>{,<arg>}+);<body>

The <option> may be algebraic or symbolic, indicating the mode under which the procedure is executed, or real or integer, indicating the type of answer expect ed. The default is algebraic. Real or integer procedures are subtypes of algebraic procedures; type-checking is done on the results of integer procedures, but not on real procedures (in the current REDUCE release). <identifier> may be any valid REDUCE identifier that is not already a procedure name, operator, array or matrix. <arg> is a formal parameter that may be any valid REDUCE identifier. <body> is a single statement (a group or block statement may be used) with the desired activities in it.

examples:


procedure fac(n);
   if not (fixp(n) and n>=0)
     then rederr "Choose nonneg. integer only"
    else for i := 0:n-1 product i+1;

			 

  FAC 


fac(0); 

  1 


fac(5); 

  120 


fac(-5); 

  ***** choose nonneg. integer only

Procedures are automatically declared as operators upon definition . When REDUCE has parsed the procedure definition and successfully converted it to a form for its own use, it prints the name of the procedure. Procedure definitions cannot be nested. Procedures can call other procedures, or can recursively call themselves. Procedure identifiers can be cleared as you would clear an operator. Unlike let statements, new definitions under the same procedure name replace the previous definitions completely.

Be careful not to use the name of a system operator for your own procedure. REDUCE may or may not give you a warning message. If you redefine a system operator in your own procedure, the original function of the system operator is lost for the remainder of the REDUCE session.

Procedures may have none, one, or more than one parameter. A REDUCE parameter is a formal parameter only; the use of x as a parameter in a procedure definition has no connection with a value of x in the REDUCE session, and the results of calling a procedure have no effect on the value of x. If a procedure is called with x as a parameter, the current value of x is used as specified in the computation, but is not changed outside the procedure. Making an assignment statement by := with a formal parameter on the left-hand side only changes the value of the calling parameter within the procedure.

Using a let statement inside a procedure always chang es the value globally: a let with a formal parameter makes the change to the calling parameter. let statements cannot be made on local variables inside begin...end blocks. When clear statements are used on formal parameters, the calling variables associated with them are cleared globally too. The use of let or clear statements inside procedures should be done with extreme caution.

Arrays and operators may be used as parameters to procedures. The body of the procedure can contain statements that appropriately manipulate these arguments. Changes are made to values of the calling arrays or operators. Simple expressions can also be used as arguments, in the place of scalar variables. Matrices may not be used as arguments to procedures.

A procedure that has no parameters is called by the procedure name, immediately followed by empty parentheses. The empty parentheses may be left out when writing a procedure with no parameters, but must appear in a call of the procedure. If this is a nuisance to you, use a let statement on the name of the procedure (i.e., let noargs = noargs()) after which you can call the procedure by just its name.

Procedures that have a single argument can leave out the parentheses around it both in the definition and procedure call. (You can use the parentheses if you wish.) Procedures with more than one argument must use parentheses, with the arguments separated by commas.

Procedures often have a begin...end block in them. Inside the block, local variables are declared using scalar, real or integer declarations. The declarations must be made immediately after the word begin, and if more than one type of declaration is made, they are separated by semicolons. REDUCE currently does no type checking on local variables; real and integer are treated just like scalar . Actions take place as specified in the statements inside the block statement. Any identifiers that are not formal parameters or local variables are treated as global variables, and activities involving these identifiers are global in effect.

If a return value is desired from a procedure call, a specific return command must be the last statement exe cuted before exiting from the procedure. If no return is used, a procedure returns a zero or no value.

Procedures are often written in a file using an editor, then the file is input using the command in. This method allows easy changes in development, and also allows you to load the named procedures whenever you like, by loading the files that contain them.

REPEAT

REDUC
E

INDEX

REPEAT _ _ _ _ _ _ _ _ _ _ _ _ command

The repeat command causes repeated execution of a statement until

the given condition is found to be true. The statement is always executed at least once.

syntax:

repeat<statement> until <condition>

<statement> can be a single statement, group statement, or a begin...end block. <condition> must be a logical operator that evaluates to true or nil.

examples:


<<m := 4; repeat <<write 100*x*m;m := m-1>> until m = 0>
>;
			 


  400*X
  300*X
  200*X
  100*X



<<m := -1; repeat <<write m; m := m-1>> until m <= 0>
>;
			 


  -1

repeatmust always be followed by an until with a condition. Be careful not to generate an infinite loop with a condition that is never true. In the second example, if the condition had been m = 0, it would never have been true since m already had value -2 when the condition was first evaluated.

REST

REDUC
E

INDEX

REST _ _ _ _ _ _ _ _ _ _ _ _ operator

The rest operator returns a list containing all but the first element of the list it is given.

syntax:

rest(<list>) or rest <list>

<list> must be a non-empty list, but need not have more than one element.

examples:


alist := {a,b,c,d}; 

  ALIST := {A,B,C,D}; 


rest alist; 

  {B,C,D} 


blist := {x,y,{aa,bb,cc},z}; 

  BLIST := {X,Y,{AA,BB,CC},Z} 


second rest blist; 

  {AA,BB,CC} 


clist := {c}; 

  CLIST := C 


rest clist; 

  {}

RETURN

REDUC
E

INDEX

RETURN _ _ _ _ _ _ _ _ _ _ _ _ command

The return command causes a value to be returned from inside a begin...end block.

syntax:

begin<statements> return <(expression)> end

<statements> can be any valid REDUCE statements. The value of <expression> is returned.

examples:


begin write "yes"; return a end; 

  yes
  A


procedure dumb(a);
  begin if numberp(a) then return a else return 10 end;

						 

  DUMB 


dumb(x); 

  10 


dumb(-5); 

  -5  


procedure dumb2(a);
  begin c := a**2 + 2*a + 1; d := 17; c*d; return end;
		 

  DUMB2 


dumb2(4); 

c; 

  25 


d; 

  17

Note in dumb2 above that the assignments were made as req uested, but the product c*d cannot be accessed. Changing the procedure to read return c*d would remedy this problem.

The return statement is always the last statement executed before leaving the block. If return has no argument, the block is exited but no value is returned. A block statement does not need a return ; the statements inside terminate in their normal fashion without one. In that case no value is returned, although the specified actions inside the block take place.

The return command can be used inside <<...>> group statements and if...then...else commands t hat are inside begin...end blocks. It is not valid in these constructions that are not inside a begin...end block. It is not valid inside for, repeat...until or while...do loops in any construction. To force early termination from loops, the go to( goto) command must be used. When you use nested block statements, a return from an inner block exits returning a value to the next-outermos t block, rather than all the way to the outside.

REVERSE

REDUC
E

INDEX

REVERSE _ _ _ _ _ _ _ _ _ _ _ _ operator

The reverse operator returns a list that is the reverse of the list it is given.

syntax:

reverse(<list>) or reverse <list>

<list> must be a list.

examples:


aa := {c,b,a,{x**2,z**3},y}; 

                 2  3
  AA := {C,B,A,{X ,Z },Y} 


reverse aa; 

       2  3
  {Y,{X ,Z },A,B,C} 


reverse(q . reverse aa); 

           2  3
  {C,B,A,{X ,Z },Y,Q}

reverseand cons can be used together to add a new elemen t to the end of a list (. adds its new element to the beginning). The reverse operator uses a noticeable amount of system resources, especially if the list is long. If you are doing much heavy-duty list manipulation, you should probably design your algorithms to avoid much reversing of lists. A moderate amount of list reversing is no problem.

RULE

REDUC
E

INDEX

RULE _ _ _ _ _ _ _ _ _ _ _ _ type

A rule is an instruction to replace an algebraic expression or a part of an expression by another one.

syntax:

<lhs> => <rhs> or <lhs> => <rhs> when <cond>

<lhs> is an algebraic expression used as search pattern and <rhs> is an algebraic expression which replaces matches of <rhs>. => is the operator replace.

<lhs> can contain free variables which are symbols preceded by a tilde ~ in their leftmost position in <lhs>. A double tilde marks an optional free variable. If a rule has a when <cond> part it will fire only if the evaluation of <cond> has a result true. <cond> may contain references to free variables of <lhs>.

Rules can be collected in a list which then forms a rule list. Rule lists can be used to collect algebraic knowledge for a specific evaluation context.

Rulesand rule lists are globally activated and deactivated by let, forall, clearrules. For a single evaluation they can be locally activate by where. The active rules for an operator can be visualized by showrules.

examples:


operator f,g,h; 

let f(x) => x^2; 

f(x); 

   2
  x


g_rules:={g(~n,~x)=>h(n/2,x) when evenp n,

g(~n,~x)=>h((1-n)/2,x) when not evenp n}$

let g_rules;

g(3,x); 

  h(-1,x)

Free_Variable

REDUC
E

INDEX

FREE VARIABLE _ _ _ _ _ _ _ _ _ _ _ _ type

A variable preceded by a tilde is considered as free variable and stands for an arbitrary part in an algebraic form during pattern matching. Free variables occur in the left-hand sides of rules, in the side relations for compact and in the first arguments of map and select calls. See rule for examples.

In rules also optional free variables may occur.

Optional_Free_Variable

REDUC
E

INDEX

OPTIONAL FREE VARIABLE _ _ _ _ _ _ _ _ _ _ _ _ type

A variable preceded by a double tilde is considered as optional free variable

and stands for an arbitrary part part in an algebraic form during pattern matching. In contrast to ordinary free variables an operator pattern with an optional free variable matches also if the operand for the variable is missing. In such a case the variable is bound to a neutral value. Optional free variables can be used as

term in a sum: set to 0 if missing,

factor in a product: set to 1 if missing,

exponent: set to 1 if missing

examples:

Optional free variables are allowed only in the left-h and sides of rules.

SECOND

REDUC
E

INDEX

SECOND _ _ _ _ _ _ _ _ _ _ _ _ operator

The second operator returns the second element of a list.

syntax:

second(<list>) or second <list>

<list> must be a list with at least two elements, to avoid an error message.

examples:


alist := {a,b,c,d}; 

  ALIST := {A,B,C,D} 


second alist; 

  B 


blist := {x,{aa,bb,cc},z}; 

  BLIST := {X,{AA,BB,CC},Z} 


second second blist; 

  BB

SET

REDUC
E

INDEX

SET _ _ _ _ _ _ _ _ _ _ _ _ operator

The set operator is used for assignments when you want both sides of the assignment statement to be evaluated.

syntax:

set(<restricted\_expression>,<expression>)

<expression> can be any REDUCE expression; <restricted\_expression> must be an identifier or an expression that evaluates to an identifier.

examples:


a := y; 

  A := Y 


set(a,sin(x^2)); 

       2
  SIN(X ) 


a; 

       2
  SIN(X ) 


y; 

       2
  SIN(X ) 


a := b + c; 

  A := B + C 


set(a-c,z); 

  Z 


b; 

  Z

Using an array or matrix reference as the first argument to set has the result of setting the contents of the designated element to set's second argument. You should be careful to avoid unwanted side effects when you use this facility.

SETQ

REDUC
E

INDEX

SETQ _ _ _ _ _ _ _ _ _ _ _ _ operator

The setq operator is an infix or prefix binary assignment operator. It is identical to :=.

syntax:

setq(<restricted\_expression>,<expression>) or

<restricted\_expression> setq <expression>

<restricted expression> is ordinarily a single identifier, though simple expressions may be used (see Comments below). <expression> can be any valid REDUCE expression. If <expression> is a matrix identifier, then <restricted\_expression> can be a matrix identifier (redimensioned if necessary), which has each element set to the corresponding elements of the identifier on the right-hand side.

examples:


setq(b,6); 

  B := 6 


c setq sin(x); 

  C := SIN(X) 


w + setq(c,x+3) + z; 

  W + X + Z + 3 


c; 

  X + 3 


setq(a1 + a2,25); 

  A1 + A2 := 25 


a1; 

  - (A2 - 25)

Embedding a setq statement in an expression has the side effect of making the assignment, as shown in the third example above.

Assignments are generally done for identifiers, but may be done for simple expressions as well, subject to the following remarks:

_ _ _ (i) If the left-hand side is an identifier, an operator, or a power, the rule is added to the rule table.

_ _ _ (ii) If the operators - + / appear on the left-hand side, all but the first term of the expression is moved to the right-hand side.

_ _ _ (iii) If the operator * appears on the left-hand side, any constant terms are moved to the right-hand side, but the symbolic factors remain.

Be careful not to make a recursive setq assignment that is not controlled inside a loop statement. The process of resubstitution continues until you get a stack overflow message. setq can be used to attach functionality to operators, as the := does.

THIRD

REDUC
E

INDEX

THIRD _ _ _ _ _ _ _ _ _ _ _ _ operator

The third operator returns the third item of a list.

syntax:

third(<list>) or third <list>

<list> must be a list containing at least three items to avoid an error message.

examples:


alist := {a,b,c,d}; 

  ALIST := {A,B,C,D} 


third alist; 

  C 


blist := {x,{aa,bb,cc},y,z}; 

  BLIST := {X,{AA,BB,CC},Y,Z}; 


third second blist; 

  CC 


third blist; 

  Y

WHEN

REDUC
E

INDEX

WHEN _ _ _ _ _ _ _ _ _ _ _ _ operator

The when operator is used inside a rule to make the execution of the rule depend on a boolean condition which is evaluated at execution time. For the use see rule.

Syntax

REDUC
E

INDEX

Syntax

  • semicolon commandalias= (;)

  • dollar commandalias= ($)

  • percent commandalias= (%)

  • dot operatoralias= (.)

  • assign operatoralias= (: =)

  • equalsign operatoralias= (=)

  • replace operatoralias= (= >)

  • plussign operatoralias= (+)

  • minussign operatoralias= (-)

  • asterisk operatoralias= (*)

  • slash operatoralias= (/)

  • power operatoralias= (* *)

  • caret operatoralias= (^)

  • geqsign operatoralias= (> =)

  • greater operatoralias= (>)

  • leqsign operatoralias= (< =)

  • less operatoralias= (<)

  • tilde operatoralias= (~)

  • group commandalias= (< <)

  • AND operator

  • BEGIN command

  • block command

  • COMMENT command

  • CONS operator

  • END command

  • EQUATION type

  • FIRST operator

  • FOR command

  • FOREACH command

  • GEQ operator

  • GOTO command

  • GREATERP operator

  • IF command

  • LIST operator

  • OR operator

  • PROCEDURE command

  • REPEAT command

  • REST operator

  • RETURN command

  • REVERSE operator

  • RULE type

  • Free Variable type

  • Optional Free Variable type

  • SECOND operator

  • SET operator

  • SETQ operator

  • THIRD operator

  • WHEN operator

  • ARITHMETIC_OPERATIONS

    REDUC
E

    INDEX

    ARITHMETIC\_OPERATIONS _ _ _ _ _ _ _ _ _ _ _ _ introduction

    This section considers operations defined in REDUCE that concern numbers, or operators that can operate on numbers in addition, in most cases, to more general expressions.

    ABS

    REDUC
E

    INDEX

    ABS _ _ _ _ _ _ _ _ _ _ _ _ operator

    The abs operator returns the absolute value of its argument.

    syntax:

    abs(<expression>)

    <expression> can be any REDUCE scalar expression.

    examples:

    
    abs(-a); 
    
      ABS(A) 
    
    
    abs(-5); 
    
      5 
    
    
    a := -10; 
    
      A := -10 
    
    
    abs(a); 
    
      10 
    
    
    abs(-a); 
    
      10
    
    

    If the argument has had no numeric value assigned to it, such as a n identifier or polynomial, abs returns an expression involving abs of its argument, doing as much simplification of the argument as it can, such as dropping any preceding minus sign.

    ADJPREC

    REDUC
E

    INDEX

    ADJPREC _ _ _ _ _ _ _ _ _ _ _ _ switch

    When a real number is input, it is normally truncated to the precision in effect at the time the number is read. If it is desired to keep the full precision of all numbers input, the switch adjprec (for <adjust precision>) can be turned on. While on, adjprec will automatically increase the precision, when necessary, to match that of any integer or real input, and a message printed to inform the user of the precision increase.

    examples:

    
    on rounded; 
    
    1.23456789012345; 
    
      1.23456789012 
    
    
    on adjprec; 
    
    1.23456789012345; 
    
    *** precision increased to 15 
    

    ARG

    REDUC
E

    INDEX

    ARG _ _ _ _ _ _ _ _ _ _ _ _ operator

    If complex and rounded are on, and arg evaluates to a complex number, arg returns the polar angle of arg, measured in radians. Otherwise an expression in arg is returned.

    examples:

    
    arg(3+4i) 
    
      ARG(3 + 4*I) 
    
    
    on rounded, complex; 
    
    ws; 
    
      0.927295218002 
    
    
    arg a; 
    
      ARG(A)
    
    

    CEILING

    REDUC
E

    INDEX

    CEILING _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    ceiling(<expression>)

    This operator returns the ceiling (i.e., the least integer greater than or equal to its argument) if its argument has a numerical value. For negative numbers, this is equivalent to fix. For non-numeric arguments, the value is an expression in the original operator.

    examples:

    
    ceiling 3.4; 
    
      4 
    
    
    fix 3.4; 
    
      3 
    
    
    ceiling(-5.2); 
    
      -5 
    
    
    fix(-5.2); 
    
      -5 
    
    
    ceiling a; 
    
      CEILING(A)
    
    

    CHOOSE

    REDUC
E

    INDEX

    CHOOSE _ _ _ _ _ _ _ _ _ _ _ _ operator

    choose(<m>,<m>) returns the number of ways of choosing <m> objects from a collection of <n> distinct objects --- in other words the binomial coefficient. If <m> and <n> are not positive integers, or m >n, the expression is returned unchanged. than or equal to

    examples:

    
    choose(2,3); 
    
      3 
    
    
    choose(3,2); 
    
      CHOOSE(3,2) 
    
    
    choose(a,b); 
    
      CHOOSE(A,B)
    
    

    DEG2DMS

    REDUC
E

    INDEX

    DEG2DMS _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    deg2dms(<expression>)

    In rounded mode, if <expression> is a real number, the operator deg2dms will interpret it as degrees, and convert it to a list containing the equivalent degrees, minutes and seconds. In all other cases, an expression in terms of the original operator is returned.

    examples:

    
    deg2dms 60; 
    
      DEG2DMS(60) 
    
    
    on rounded; 
    
    ws; 
    
      {60,0,0} 
    
    
    deg2dms 42.4; 
    
      {42,23,60.0} 
    
    
    deg2dms a; 
    
      DEG2DMS(A)
    
    

    DEG2RAD

    REDUC
E

    INDEX

    DEG2RAD _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    deg2rad(<expression>)

    In rounded mode, if <expression> is a real number, the operator deg2rad will interpret it as degrees, and convert it to the equivalent radians. In all other cases, an expression in terms of the original operator is returned.

    examples:

    
    deg2rad 60; 
    
      DEG2RAD(60) 
    
    
    on rounded; 
    
    ws; 
    
      1.0471975512 
    
    
    deg2rad a; 
    
      DEG2RAD(A)
    
    

    DIFFERENCE

    REDUC
E

    INDEX

    DIFFERENCE _ _ _ _ _ _ _ _ _ _ _ _ operator

    The difference operator may be used as either an infix or prefix binary subtraction operator. It is identical to - as a binary operator.

    syntax:

    difference(<expression>,<expression>) or

    <expression> difference <expression> {difference <expression>}*

    <expression> can be a number or any other valid REDUCE expression. Matrix expressions are allowed if they are of the same dimensions.

    examples:

    
    
    difference(10,4); 
    
      6 
    
    
    
    15 difference 5 difference 2; 
    
      8 
    
    
    
    a difference b; 
    
      A - B
    
    

    The difference operator is left associative, as shown in the second example above.

    DILOG

    REDUC
E

    INDEX

    DILOG _ _ _ _ _ _ _ _ _ _ _ _ operator

    The dilog operator is known to the differentiation and integration operators, but has numeric value attached only at dilog(0). Dilog is defined by

    dilog(x) = -int(log(x),x)/(x-1)

    examples:

    
    df(dilog(x**2),x); 
    
               2
        2*LOG(X )*X
      - ------------
           2
          X   - 1
    
    
    
    int(dilog(x),x); 
    
      DILOG(X)*X - DILOG(X) + LOG(X)*X - X 
    
    
    
    dilog(0); 
    
        2
      PI
      ----
       6
    
    

    DMS2DEG

    REDUC
E

    INDEX

    DMS2DEG _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    dms2deg(<list>)

    In rounded mode, if <list> is a list of th ree real numbers, the operator dms2deg will interpret the list as degrees, minutes and seconds and convert it to the equivalent degrees. In all other cases, an expression in terms of the original operator is returned.

    examples:

    
    dms2deg {42,3,7}; 
    
      DMS2DEG({42,3,7}) 
    
    
    on rounded; 
    
    ws; 
    
      42.0519444444 
    
    
    dms2deg a; 
    
      DMS2DEG(A)
    
    

    DMS2RAD

    REDUC
E

    INDEX

    DMS2RAD _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    dms2rad(<list>)

    In rounded mode, if <list> is a list of th ree real numbers, the operator dms2rad will interpret the list as degrees, minutes and seconds and convert it to the equivalent radians. In all other cases, an expression in terms of the original operator is returned.

    examples:

    
    dms2rad {42,3,7}; 
    
      DMS2RAD({42,3,7}) 
    
    
    on rounded; 
    
    ws; 
    
      0.733944887421 
    
    
    dms2rad a; 
    
      DMS2RAD(A)
    
    

    FACTORIAL

    REDUC
E

    INDEX

    FACTORIAL _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    factorial(<expression>)

    If the argument of factorial is a positive integer or zero, its factorial is returned. Otherwise the result is expressed in terms of the original operator. For more general operations, the gamma operator is available in the Special Function Package.

    examples:

    
    factorial 4; 
    
      24 
    
    
    factorial 30 ; 
    
      265252859812191058636308480000000 
    
    

    FIX

    REDUC
E

    INDEX

    FIX _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    fix(<expression>)

    The operator fix returns the integer part of its argument, if that argument has a numerical value. For positive numbers, this is equivalent to floor, and, for negative numbers, ceiling. For non-numeric arguments, the value is an expression in the original operator.

    examples:

    
    fix 3.4; 
    
      3 
    
    
    floor 3.4; 
    
      3 
    
    
    ceiling 3.4; 
    
      4 
    
    
    fix(-5.2); 
    
      -5 
    
    
    floor(-5.2); 
    
      -6 
    
    
    ceiling(-5.2); 
    
      -5 
    
    
    fix(a); 
    
      FIX(A)
    
    

    FIXP

    REDUC
E

    INDEX

    FIXP _ _ _ _ _ _ _ _ _ _ _ _ operator

    The fixp logical operator returns true if its argument is an integer.

    syntax:

    fixp(<expression>) or fixp <simple\_expression>

    <expression> can be any valid REDUCE expression, <simple\_expression > must be a single identifier or begin with a prefix operator.

    examples:

    
    if fixp 1.5 then write "ok" else write "not";
    			 
    
    
      not 
    
    
    if fixp(a) then write "ok" else write "not";
    			 
    
    
      not 
    
    
    a := 15; 
    
      A := 15 
    
    
    if fixp(a) then write "ok" else write "not";
    			 
    
    
      ok
    
    

    Logical operators can only be used inside conditional expressions such as if...then or while...do.

    FLOOR

    REDUC
E

    INDEX

    FLOOR _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    floor(<expression>)

    This operator returns the floor (i.e., the greatest integer less than or equal to its argument) if its argument has a numerical value. For positive numbers, this is equivalent to fix. For non-numeric arguments, the value is an expression in the original operator.

    examples:

    
    floor 3.4; 
    
      3 
    
    
    fix 3.4; 
    
      3 
    
    
    floor(-5.2); 
    
      -6 
    
    
    fix(-5.2); 
    
      -5 
    
    
    floor a; 
    
      FLOOR(A)
    
    

    EXPT

    REDUC
E

    INDEX

    EXPT _ _ _ _ _ _ _ _ _ _ _ _ operator

    The expt operator is both an infix and prefix binary exponentiation operator. It is identical to ^ or **.

    syntax:

    expt(<expression>,<expression>) or <expression> expt <expression>

    examples:

    
    a expt b; 
    
       B
      A  
    
    
    expt(a,b); 
    
       B
      A  
    
    
    (x+y) expt 4; 
    
       4      3        2  2        3    4
      X  + 4*X *Y + 6*X *Y  + 4*X*Y  + Y
    
    

    Scalar expressions may be raised to fractional and floating-point powers. Square matrix expressions may be raised to positive powers, and also to negative powers if non-singular.

    exptis left associative. In other words, a expt b expt c is equivalent to a expt (b*c), not a expt (b expt c), which would be right associative.

    GCD

    REDUC
E

    INDEX

    GCD _ _ _ _ _ _ _ _ _ _ _ _ operator

    The gcd operator returns the greatest common divisor of two polynomials.

    syntax:

    gcd(<expression>,<expression>)

    <expression> must be a polynomial (or integer), otherwise an error occurs.

    examples:

    
    gcd(2*x**2 - 2*y**2,4*x + 4*y); 
    
      2*(X + Y) 
    
    
    gcd(sin(x),x**2 + 1); 
    
      1  
    
    
    gcd(765,68); 
    
      17
    
    

    The operator gcd described here provides an explicit mean s to find the gcd of two expressions. The switch gcd described below simplifies expressions by finding and canceling gcd's at every opportunity. When the switch ezgcd is also on, gcd's are figured using the EZ GCD algorithm, which is usually faster.

    LN

    REDUC
E

    INDEX

    LN _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    ln(<expression>)

    <expression> can be any valid scalar REDUCE expression.

    The ln operator returns the natural logarithm of its argument. However, unlike log, there are no algebraic rules associated with it; it will only evaluate when rounded is on, and the argument is a real number.

    examples:

    
    ln(x); 
    
      LN(X) 
    
    
    ln 4; 
    
      LN(4) 
    
    
    ln(e); 
    
      LN(E) 
    
    
    df(ln(x),x); 
    
      DF(LN(X),X) 
    
    
    on rounded; 
    
    ln 4; 
    
      1.38629436112 
    
    
    ln e; 
    
      1
    
    

    Because of the restricted algebraic properties of ln, use rs are advised to use log whenever possible.

    LOG

    REDUC
E

    INDEX

    LOG _ _ _ _ _ _ _ _ _ _ _ _ operator

    The log operator returns the natural logarithm of its argument.

    syntax:

    log(<expression>) or log <expression>

    <expression> can be any valid scalar REDUCE expression.

    examples:

    
    log(x); 
    
      LOG(X) 
    
    
    log 4; 
    
      LOG(4) 
    
    
    log(e); 
    
      1 
    
    
    on rounded; 
    
    log 4; 
    
      1.38629436112
    
    

    logreturns a numeric value only when rounded is on. In that case, use of a negative argument for log results in an error message. No error is given on a negative argument when REDUCE is not in that mode.

    LOGB

    REDUC
E

    INDEX

    LOGB _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    logb(<expression>,<integer>)

    <expression> can be any valid scalar REDUCE expression.

    The logb operator returns the logarithm of its first argument using the second argument as base. However, unlike log, there are no algebraic rules associated with it; it will only evaluate when rounded is on, and the first argument is a re al number.

    examples:

    
    logb(x,2); 
    
      LOGB(X,2) 
    
    
    logb(4,3); 
    
      LOGB(4,3) 
    
    
    logb(2,2); 
    
      LOGB(2,2) 
    
    
    df(logb(x,3),x); 
    
      DF(LOGB(X,3),X) 
    
    
    on rounded; 
    
    logb(4,3); 
    
      1.26185950714 
    
    
    logb(2,2); 
    
      1
    
    

    MAX

    REDUC
E

    INDEX

    MAX _ _ _ _ _ _ _ _ _ _ _ _ operator

    The operator max is an n-ary prefix operator, which returns the largest value in its arguments.

    syntax:

    max(<expression>{,<expression>}*)

    <expression> must evaluate to a number. max of an empty list returns 0.

    examples:

    
    max(4,6,10,-1); 
    
      10 
    
    
    <<a := 23;b := 2*a;c := 4**2;max(a,b,c)>>;
    			 
    
    
      46 
    
    
    max(-5,-10,-a); 
    
      -5
    
    

    MIN

    REDUC
E

    INDEX

    MIN _ _ _ _ _ _ _ _ _ _ _ _ operator

    The operator min is an n-ary prefix operator, which returns the smallest value in its arguments.

    syntax:

    min(<expression>{,<expression>}*)

    <expression> must evaluate to a number. min of an empty list returns 0.

    examples:

    
    min(-3,0,17,2); 
    
      -3 
    
    
    <<a := 23;b := 2*a;c := 4**2;min(a,b,c)>>;
    			 
    
    
      16 
    
    
    min(5,10,a); 
    
      5
    
    

    MINUS

    REDUC
E

    INDEX

    MINUS _ _ _ _ _ _ _ _ _ _ _ _ operator

    The minus operator is a unary minus, returning the negative of its argument. It is equivalent to the unary -.

    syntax:

    minus(<expression>)

    <expression> may be any scalar REDUCE expression.

    examples:

    
    minus(a); 
    
      - A 
    
    
    minus(-1); 
    
      1 
    
    
    minus((x+1)**4); 
    
          4      3      2
      - (X  + 4*X  + 6*X  + 4*X + 1)
    
    

    NEXTPRIME

    REDUC
E

    INDEX

    NEXTPRIME _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    nextprime(<expression>)

    If the argument of nextprime is an integer, the least prime greater than that argument is returned. Otherwise, a type error results.

    examples:

    
    nextprime 5001; 
    
      5003  
    
    
    nextprime(10^30); 
    
      1000000000000000000000000000057 
    
    
    nextprime a; 
    
      ***** A invalid as integer
    
    

    NOCONVERT

    REDUC
E

    INDEX

    NOCONVERT _ _ _ _ _ _ _ _ _ _ _ _ switch

    Under normal circumstances when rounded is on, REDUCE converts the number 1.0 to the integer 1. If this is not desired, the switch noconvert can be turned on.

    examples:

    
    on rounded; 
    
    1.0000000000001; 
    
      1 
    
    
    on noconvert; 
    
    1.0000000000001; 
    
      1.0 
    
    

    NORM

    REDUC
E

    INDEX

    NORM _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    norm(<expression>)

    If rounded is on, and the argument is a real number, <norm> returns its absolute value. If complex is also on, <norm> returns the square root of the sum of squares of the real and imaginary parts of the argument. In all other cases, a result is returned in terms of the original operator.

    examples:

    
    norm (-2); 
    
      NORM(-2) 
    
    
    on rounded;
    
    ws; 
    
      2.0 
    
    
    norm(3+4i); 
    
      NORM(4*I+3) 
    
    
    on complex;
    
    ws; 
    
      5.0
    
    

    PERM

    REDUC
E

    INDEX

    PERM _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    perm(<expression1>,<expression2>)

    If <expression1> and <expression2> evaluate to positive integers, perm returns the number of permutations possible in selecting <expression1> objects from <expression2> objects. In other cases, an expression in the original operator is returned.

    examples:

    
    perm(1,1); 
    
      1 
    
    
    perm(3,5); 
    
      60 
    
    
    perm(-3,5); 
    
      PERM(-3,5) 
    
    
    perm(a,b); 
    
      PERM(A,B)
    
    

    PLUS

    REDUC
E

    INDEX

    PLUS _ _ _ _ _ _ _ _ _ _ _ _ operator

    The plus operator is both an infix and prefix n-ary addition operator. It exists because of the way in which REDUCE handles such operators internally, and is not recommended for use in algebraic mode programming. plussign, which has the identical effect, sho uld be used instead.

    syntax:

    plus(<expression>,<expression>{,<expression>} *) or

    <expression> plus <expression> {plus <expressio n>}*

    <expression> can be any valid REDUCE expression, including matrix expressions of the same dimensions.

    examples:

    
    a plus b plus c plus d; 
    
      A + B + C + D 
    
    
    4.5 plus 10; 
    
      29
      -- 
      2
    
    
    
    plus(x**2,y**2); 
    
       2    2
      X  + Y
    
    

    QUOTIENT

    REDUC
E

    INDEX

    QUOTIENT _ _ _ _ _ _ _ _ _ _ _ _ operator

    The quotient operator is both an infix and prefix binary operator that returns the quotient of its first argument divided by its second. It is also a unary reciprocal operator. It is identical to / and slash.

    syntax:

    quotient(<expression>,<expression>) or <expression> quotient <expression> or quotient(<expression>) or quotient <expression>

    <expression> can be any valid REDUCE scalar expression. Matrix expressions can also be used if the second expression is invertible and the matrices are of the correct dimensions.

    examples:

    
    quotient(a,x+1); 
    
        A
      ----- 
      X + 1
    
    
    7 quotient 17; 
    
      7
      -- 
      17
    
    
    on rounded; 
    
    4.5 quotient 2; 
    
      2.25 
    
    
    quotient(x**2 + 3*x + 2,x+1); 
    
      X + 2 
    
    
    matrix m,inverse; 
    
    m := mat((a,b),(c,d)); 
    
      M(1,1) := A;
      M(1,2) := B;
      M(2,1) := C
      M(2,2) := D
    
    
    
    inverse := quotient m; 
    
                          D
      INVERSE(1,1) := ----------
                      A*D - B*C
                            B
      INVERSE(1,2) := - ----------
                        A*D - B*C
                            C
      INVERSE(2,1) := - ----------
                        A*D - B*C
                          A
      INVERSE(2,2) := ----------
                      A*D - B*C
    
    

    The quotient operator is left associative: a quotient b quotient c is equivalent to (a quotient b) quotient c.

    If a matrix argument to the unary quotient is not invertible, or if the second matrix argument to the binary quotient is not invertible, an error message is given.

    RAD2DEG

    REDUC
E

    INDEX

    RAD2DEG _ _ _ _ _ _ _ _ _ _ _ _ operator

    syntax:

    rad2deg(<expression>)

    In rounded mode, if <expression> is a real number, the operator rad2deg will interpret it as radians, and convert it to the equivalent degrees. In all other cases, an expression in terms of the original operator is returned.

    examples:

    
    rad2deg 1; 
    
      RAD2DEG(1) 
    
    
    on rounded; 
    
    ws; 
    
      57.2957795131 
    
    
    rad2deg a; 
    
      RAD2DEG(A)