less4 22 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545
  1. COMMENT
  2. REDUCE INTERACTIVE LESSON NUMBER 4
  3. David R. Stoutemyer
  4. University of Hawaii
  5. COMMENT This is lesson 4 of 7 REDUCE lessons. As before, please
  6. refrain from using variables beginning with the letters F through H
  7. during the lesson.
  8. In theory, assignments and LET statements are sufficient to
  9. accomplish anything that any other practical computing mechanism is
  10. capable of doing. However, it is more convenient for some purposes
  11. to use function procedures which can employ branched selection and
  12. iteration as do most traditional programming languages. As a trivial
  13. example, if we invariably wanted to replace cotangents with the
  14. corresponding tangents, we could type;
  15. ALGEBRAIC PROCEDURE COT(X); 1/TAN(X);
  16. COMMENT As an example of the use of this function, we have;
  17. COT(LOG(F));
  18. COMMENT Note:
  19. 1. The procedure definition automatically declares the procedure
  20. name as an operator.
  21. 2. A procedure can be executed any time after its definition,
  22. until it is cleared.
  23. 3. Any parameters are dummy variables that are distinct from
  24. any other variables with the same name outside the procedure
  25. definition, and the corresponding arguments can be
  26. arbitrary expressions.
  27. 4. The value returned by a procedure is the value of the
  28. expression following the procedure statement.
  29. We can replace this definition with a different one;
  30. ALGEBRAIC PROCEDURE COT(Y); COS(Y)/SIN(Y);
  31. G1:= COT(LOG(F));
  32. COMMENT In place of the word ALGEBRAIC, we can optionally use the
  33. word INTEGER when a function always returns an integer value, or we
  34. can optionally use the word REAL when a function always returns a
  35. floating-point value.
  36. Try writing a procedure definition for the sine in terms of the
  37. cosine, then type G1;
  38. PAUSE;
  39. COMMENT Here is a more complicated function which introduces the
  40. notion of a conditional expression;
  41. ALGEBRAIC PROCEDURE SUMCHECK(AJ, J, M, N, S);
  42. COMMENT J is an indeterminate and the other parameters are
  43. expressions. This function returns the global variable named
  44. PROVED if the function can inductively verify that S equals the
  45. sum of AJ for J going from M through N, returning the global
  46. variable named UNPROVED otherwise. For the best chance of
  47. proving a correct sum, the function should be executed under
  48. the influence of ON EXP, ON MCD, and any other user-supplied
  49. simplification rules relevant to the expression classes of AJ
  50. and S;
  51. IF SUB(J=M,AJ)-SUB(N=M,S) NEQ 0
  52. OR S+SUB(J=N+1,AJ)-SUB(N=N+1,S) NEQ 0 THEN UNPROVED
  53. ELSE PROVED;
  54. ON EXP, MCD;
  55. CLEAR X, J, N;
  56. SUMCHECK(J, J, 1, N, N*(N+1)/2);
  57. SUMCHECK(X**J, J, 0, N, (X**(N+1)-1)/(X-1));
  58. COMMENT Within procedures of this sort a global variable is any
  59. variable which is not one of the parameters, and a global variable
  60. has the value, if any, which is current for that name at the point
  61. from where the procedure is used. Conditional expressions have the
  62. form
  63. IF condition THEN expression1 ELSE expression2.
  64. There are generally several equivalent ways of writing a conditional
  65. expression. For example, the body of the above procedure could have
  66. been written
  67. IF SUB(J=M,A)-SUB(N=M,S)=0 AND S+SUB(J=N+1,A)-SUB(N=N+1,S)=0
  68. THEN PROVED
  69. ELSE UNPROVED.
  70. Note how we compare a difference with 0, rather than comparing
  71. two nonzero expressions, for reasons explained in lesson 3.
  72. As an exercise, write a procedure analogous to SUMCHECK for proving
  73. closed-form product formulas, then test it on the valid formula that
  74. COS(N*X) equals the product of COS(J*X)/COS(J*X-X) for J ranging from
  75. 1 through N. You do not need to include prefatory comments
  76. describing parameters and the returned value until you learn how to
  77. use a text editor;
  78. PAUSE;
  79. COMMENT Most REDUCE statements are also expressions because they have
  80. a value. The value is usually 0 if nothing else makes sense, but I
  81. will mention the value only if it is useful.
  82. The value of an assignment statement is the assigned value. Thus a
  83. multiple assignment, performed right to left, can be achieved by a
  84. sequence of the form
  85. "variable1 := variable2 := ... := variableN := expression",
  86. moreover, assignments can be inserted within ordinary expressions
  87. such as X*(Y:=5). Such assignments must usually be parenthesized
  88. because of the low precedence of the assignment operator, and
  89. excessive use of this construct tends to make programs confusing.
  90. REDUCE treats as a single expression any sequence of statements
  91. preceded by the pair of adjacent characters << and followed by the
  92. pair >>. The value of such a group expression is the value of the
  93. last statement in the group.
  94. Group expressions facilitate the implementation of tasks that are
  95. most easily stated as a sequence of operations. However, such
  96. sequences often utilize temporary variables to count, hold
  97. intermediate results, etc., and it is hazardous to use global
  98. variables for that purpose. If a top-level REDUCE statement or
  99. another function directly or indirectly uses that variable name, then
  100. its value or its virgin indeterminate status there might be damaged
  101. by our use as a temporary variable. In large programs or programs
  102. which rely on the work of others, such interference has a
  103. nonnegligible probability, even if all programmers agree to the
  104. convention that all such temporary variables should begin with the
  105. function name as a prefix and all programmers attempt to comply with
  106. the convention. For this reason, REDUCE provides another
  107. expression-valued sequence called a BEGIN-block, which permits the
  108. declaration of local variables that are distinct from any other
  109. variables outside the block having the same name. Another advantage
  110. of using local variables for temporary variables is that the perhaps
  111. large amount of storage occupied by their values can be reclaimed
  112. after leaving their block.
  113. A BEGIN-block consists of the word BEGIN, followed by optional
  114. declarations, followed by a sequence of statements, followed by the
  115. word END. As a convenience, any text from the word END to the next
  116. statement separator, >>, END, ELSE, or UNTIL is a comment. Within
  117. BEGIN-blocks, it is often convenient to return control and a value
  118. from someplace other than the end of the block rather than have the
  119. value be that of the last statement. Consequently, control and a
  120. value must be returned via a RETURN-statement or the form
  121. RETURN expression
  122. or
  123. RETURN,
  124. 0 being returned in the latter case.
  125. These features and others are illustrated by the following function;
  126. PAUSE;
  127. ALGEBRAIC PROCEDURE LIMIT(EX, INDET, PNT);
  128. BEGIN COMMENT This function uses up through 4 iterations of
  129. L'Hospital's rule to attempt determination of the limit of
  130. expression EX as indeterminate INDET approaches expression
  131. PNT. This function is intended for the case where
  132. SUB(INDET=PNT, EX) yields 0/0, provoking a zero-divide
  133. message. This function returns the global variable named
  134. UNDEFINED when the limit is 0 dividing an expression which did
  135. not simplify to 0, and this function returns the global
  136. variable named UNKNOWN when it cannot determine the limit.
  137. Otherwise this function returns an expression which is the
  138. limit. For best results, this function should be executed
  139. under the influence of ON EXP, ON MCD, and any user-supplied
  140. simplification rules appropriate to the expression classes of
  141. EX and PNT;
  142. INTEGER ITERATION;
  143. SCALAR N, D, NLIM, DLIM;
  144. ITERATION := 0;
  145. N := NUM(EX);
  146. D := DEN(EX);
  147. NLIM := SUB(INDET=PNT, N);
  148. DLIM := SUB(INDET=PNT, D);
  149. WHILE NLIM=0 AND DLIM=0 AND ITERATION<5 DO <<
  150. N := DF(N, INDET);
  151. D := DF(D, INDET);
  152. NLIM := SUB(INDET=PNT, N);
  153. DLIM := SUB(INDET=PNT, D);
  154. ITERATION := ITERATION + 1 >>;
  155. RETURN (IF NLIM=0 THEN
  156. IF DLIM=0 THEN UNKNOWN
  157. ELSE 0
  158. ELSE IF DLIM=0 THEN UNDEFINED
  159. ELSE NLIM/DLIM)
  160. END;
  161. % Examples follow..
  162. PAUSE;
  163. G1 := (E**X-1)/X;
  164. % Evaluation at 0, causes zero divide prompt at top level, continue
  165. % anyway.
  166. SUB(X=0, G1);
  167. LIMIT(G1, X, 0);
  168. G1:= ((1-X)/LOG(X))**2;
  169. % Evaluation at 1, causes zero divide prompt at top level, continue
  170. % anyway.
  171. SUB(X=1, G1);
  172. LIMIT(G1, X, 1);
  173. COMMENT Note:
  174. 1. The idea behind L'Hospital's rule is that as long as the
  175. numerator and denominator are both zero at the limit point, we
  176. can replace them by their derivatives without altering the
  177. limit of the quotient.
  178. 2. Assignments within groups and BEGIN-blocks do not
  179. automatically cause output.
  180. 3. Local variables are declared INTEGER, REAL, or SCALAR, the
  181. latter corresponding to the same most general class denoted by
  182. ALGEBRAIC in a procedure statement. All local variables are
  183. initialized to zero, so they cannot serve as indeterminates.
  184. Moreover, if we attempted to overcome this by clearing them,
  185. we would clear all variables with their names.
  186. 4. We do not declare the attributes of parameters.
  187. 5. The NUM and DEN functions respectively extract the numerator
  188. and denominator of their arguments. (With OFF MCD, the
  189. denominator of 1+1/X would be 1.)
  190. 6. The WHILE-loop has the general form
  191. WHILE condition DO statement.
  192. REDUCE also has a "GO TO" statement, and using commas rather
  193. than semicolons to prevent termination of this comment, the
  194. above general form of a WHILE-loop is equivalent to
  195. BEGIN GO TO TEST,
  196. LOOP: statement,
  197. TEST: IF condition THEN GO TO LOOP,
  198. RETURN 0
  199. END .
  200. A GOTO statement is permitted only within a block, and the
  201. GOTO statement cannot refer to a label outside the same block
  202. or to a label inside a block that the GOTO statement is not
  203. also within. Actually, 99.99% of REDUCE BEGIN-blocks are less
  204. confusing if written entirely without GOTOs, and I mention
  205. them primarily to explain WHILE-loops in terms of a more
  206. primitive notion.
  207. 7. The LIMIT function provides a good illustration of nested
  208. conditional expressions. Proceeding sequentially through such
  209. nests, each ELSE clause is matched with the nearest preceding
  210. unmatched THEN clause in the group or block. In order to help
  211. reveal their structure, I have consistently indented nested
  212. conditional statements, continuations of multi-line statements
  213. and loop-bodies according to one of the many staunchly
  214. defended indentation styles. However, older versions of REDUCE
  215. may ruin my elegant style. If you have such a version, I
  216. encourage you to indent nonetheless, in anticipation of a
  217. replacement for your obsolete version. (If you have an
  218. instructor, I also urge you to humor him by adopting his style
  219. for the duration of the course.)
  220. 8. PL/I programmers take note: "IF ... THEN ... ELSE ..." is
  221. regarded as one expression, and semicolons are used to
  222. separate rather than terminate statements. Moreover, BEGIN
  223. and END are brackets rather than statements, so a semicolon is
  224. never needed immediately after BEGIN, and a semicolon is
  225. necessary immediately preceding END only if the END is
  226. intended as a labeled destination for a GOTO. Within
  227. conditional expressions, an inappropriate semicolon after an
  228. END, a >>, or an ELSE-clause is likely to be one of your most
  229. prevalent mistakes.;
  230. PAUSE;
  231. COMMENT
  232. The next exercise is based on the above LIMIT function:
  233. For the sum of positive expressions AJ for J ranging from some finite
  234. initial value to infinity, the infinite series converges if the limit
  235. of the ratio SUB(J=J+1,AJ)/AJ is less than 1 as J approaches
  236. infinity. The series diverges if this limit exceeds 1, and the test
  237. is inconclusive if the limit is 1. To convert the problem to the
  238. form required by the above LIMIT program, we can replace J by the
  239. indeterminate 1/!*FOO in the ratio, then take the limit as !*FOO
  240. approaches zero. (Since an indeterminate is necessary here, I picked
  241. the weird name !*FOO to make the chance of conflict negligible)
  242. After writing such a function to perform the ratio test, test it on
  243. the examples AJ=J/2**J, AJ=1/J**2, AJ=2**J/J**10, and AJ=1/J. (The
  244. first two converge and the second two diverge);
  245. PAUSE;
  246. COMMENT Groups or blocks can be used wherever any arbitrary
  247. expression is allowed, including the right-hand side of a LET rule.
  248. The need for loops with an integer index variable running from a
  249. given initial value through a given final value by a given increment
  250. is so prevalent that REDUCE offers a convenient special way of
  251. accomplishing it via a FOR-loop, which has the general form
  252. FOR index := initial STEP increment UNTIL final DO statement .
  253. Except for the use of commas as statement separators, this construct
  254. is equivalent to
  255. BEGIN INTEGER index,
  256. index := initial,
  257. IF increment>0 THEN WHILE index <= final DO <<
  258. statement,
  259. index := index + increment >>
  260. ELSE WHILE index >= final DO <<
  261. statement,
  262. index := index + increment >>,
  263. RETURN 0
  264. END .
  265. Note:
  266. 1. The index variable is automatically declared local to the FOR-
  267. loop.
  268. 2. "initial", "increment", and "final" must have integer values.
  269. 3. FORTRAN programmers take note: the body of the loop is not
  270. automatically executed at least once.
  271. 4. An acceptable abbreviation for "STEP 1 UNTIL" is ":".
  272. 5. Since the WHILE-loop and the FOR-loop have implied BEGIN-
  273. blocks, a RETURN statement within their bodies cannot transfer
  274. control further than the point following the loops.
  275. Another frequent need is to produce output from within a group or
  276. block, because such output is not automatically produced. This can
  277. be done using the WRITE-statement, which has the form
  278. WRITE expression1, expression2, ..., expressionN.
  279. Beginning a new line with expression1, the expressions are printed
  280. immediately adjacent to each other, split over line boundaries if
  281. necessary. The value of the WRITE-statement is the value of its last
  282. expression, and any of the expressions can be a character-string
  283. of the form "character1 character2 ... characterM" .
  284. Inserting the word "WRITE" on a separate line before an assignment
  285. is convenient for debugging, because the word is then easily deleted
  286. afterward. These features and others are illustrated by the following
  287. equation solver;
  288. ARRAY CF(2);
  289. OPERATOR SOLVEFOR, SOLN;
  290. FOR ALL X, LHS, RHS LET SOLVEFOR(X, LHS, RHS) = SOLVEFOR(X, LHS-RHS);
  291. COMMENT LHS and RHS are expressions such that P=NUM(LHS-RHS) is a
  292. polynomial of degree at most 2 in the indeterminate or functional
  293. form X. Otherwise an error message is printed. As a convenience,
  294. RHS can be omitted if it is 0. If P is quadratic in X, the two
  295. values of X which satisfy P=0 are stored as the values of the
  296. functional forms SOLN(1) and SOLN(2). If P is a first-degree
  297. polynomial in X, SOLN(1) is set to the one solution. If P simplifies
  298. to 0, SOLN(1) is set to the identifier ARBITRARY. If P is an
  299. expression which does not simplify to zero but does not contain X,
  300. SOLN(1) is set to the identifier NONE. In all other cases, SOLN(1)
  301. is set to the identifier UNKNOWN. The function then returns the
  302. number of SOLN forms which were set. This function prints a well
  303. deserved warning message if the denominator of LHS-RHS contains X.
  304. This function also uses the global array CF as temporary storage. If
  305. LHS-RHS is not polynomial in X, it is wise to execute this function
  306. under the influence of ON GCD;
  307. FOR ALL X, LHSMRHS LET SOLVEFOR(X, LHSMRHS) =
  308. BEGIN INTEGER HIPOW; SCALAR TEMP;
  309. IF LHSMRHS = 0 THEN <<
  310. SOLN(1) := ARBITRARY;
  311. RETURN 1 >>;
  312. HIPOW := COEFF(LHSMRHS, X, CF);
  313. IF HIPOW = 0 THEN <<
  314. SOLN(1) := NONE;
  315. RETURN 1 >>;
  316. IF HIPOW > 2 THEN <<
  317. SOLN(1) := UNKNOWN;
  318. RETURN 1 >>;
  319. IF HIPOW = 1 THEN <<
  320. SOLN(1) := -CF(0)/CF(1);
  321. IF DF(SUB(X=!*FOO, SOLN(1)), !*FOO) NEQ 0 THEN
  322. SOLN(1) := UNKNOWN;
  323. RETURN 1 >>;
  324. CF(0) := CF(0)/CF(2);
  325. CF(1) := -CF(1)/CF(2)/2;
  326. IF DF(SUB(X=!*FOO, CF(0)), !*FOO) NEQ 0
  327. OR DF(SUB(X=!*FOO, CF(1)), !*FOO) NEQ 0 THEN <<
  328. SOLN(1) := UNKNOWN;
  329. RETURN 1 >>;
  330. TEMP := (CF(1)**2 - CF(0))**(1/2);
  331. SOLN(1) := CF(1) + TEMP;
  332. SOLN(2) := CF(1) - TEMP;
  333. RETURN 2
  334. END;
  335. FOR K:=1:SOLVEFOR(X, A*X**2, -B*X-C) DO WRITE SOLN(K) := SOLN(K);
  336. FOR K:=1:SOLVEFOR(LOG(X), 5*LOG(X)-7) DO WRITE SOLN(K) := SOLN(K);
  337. FOR K:=1:SOLVEFOR(X, X, X) DO WRITE SOLN(K) := SOLN(K);
  338. FOR K:= 1:SOLVEFOR(X, 5) DO WRITE SOLN(K) := SOLN(K);
  339. FOR K:=1:SOLVEFOR(X, X**3+X+1) DO WRITE SOLN(K) := SOLN(K);
  340. FOR K:=1:SOLVEFOR(X, X*E**X, 1) DO WRITE SOLN(K) := SOLN(K);
  341. G1 := X/(E**X-1);
  342. FOR K:=1:SOLVEFOR(X, G1) DO WRITE SOLN(K) := SOLN(K);
  343. SUB(X=SOLN(1), G1);
  344. LIMIT(G1, X, SOLN(1));
  345. COMMENT Here we have used LET rules to permit the user the
  346. convenience of omitting default arguments. (Function definitions have
  347. to have a fixed number of parameters.)
  348. Array elements are designated by the same syntax as matrix elements
  349. and as functional forms having integer arguments. Here are some
  350. desiderata that may help you decide which of these alternatives is
  351. most appropriate for a particular application:
  352. 1. The lower bound of each array subscript is 0, vs 1 for
  353. matrices vs unrestricted for functional forms.
  354. 2. The upper bound of each array subscript must have a specific
  355. integer value at the time the array is declared, as must the
  356. upper bounds of matrix subscripts when a matrix is first
  357. referred to, on the left side of a matrix assignment. In
  358. contrast, functional forms never require a commitment to a
  359. specific upper bound.
  360. 3. An array can have any fixed number of subscripts, a matrix
  361. must have exactly 2, and a functional form can have a varying
  362. arbitrary number.
  363. 4. Matrix operations, such as transpose and inverse, are built-in
  364. only for matrices.
  365. 5. For most implementations, access to array elements requires
  366. time approximately proportional to the number of subscripts,
  367. whereas access to matrix elements takes time approximately
  368. proportional to the sum of the two subscript values, whereas
  369. access to functional forms takes average time approximately
  370. proportional to the number of bound functional forms having
  371. that name.
  372. 6. Only functional forms permit the effect of a subscripted
  373. indeterminate such as having an answer be "A(M,N) + B(3,4)".
  374. 7. All arrays, matrices, and operators are global regardless
  375. of where they are declared, so declaring them within a BEGIN
  376. block does not afford the protection and automatic storage
  377. recovery of local variables. Moreover, clearing them within a
  378. BEGIN-block will clear them globally, and functions
  379. cannot return an array or a matrix value. Furthermore, REDUCE
  380. parameters are value-type parameters, which means that an
  381. assignment to a parameter has no effect on the corresponding
  382. argument. Thus, matrix or array results cannot be transmitted
  383. back to an argument either.
  384. 8. It is often advantageous to use two or more of these
  385. alternatives to represent a set of quantities at different
  386. times in the same program. For example, to get the general
  387. form of the inverse of a 3-by-3 matrix, we could write
  388. MATRIX AA,
  389. OPERATOR A,
  390. AA := MAT((0,0,0),(0,0,0),(0,0,0)),
  391. FOR J:=1:3 DO
  392. FOR K:=1:3 DO AA(J,K) := A(J,K),
  393. AA**-1 .
  394. As another example, we might use an array to receive some
  395. polynomial coefficients, then transfer the values to a matrix
  396. for inversion.
  397. The COEFF function is the remaining new feature in our SOLVEFOR
  398. example. The first argument is a polynomial expression in the
  399. indeterminate or functional form which is the second argument, and
  400. the third argument is a singly-subscripted array-name or an array
  401. cross-section for receiving the polynomial coefficients of the
  402. integer powers which correspond to their subscripts. An array
  403. cross-section is a multiply-subscripted array-reference with an
  404. asterisk as one subscript and specific integer values as the others.
  405. Examples are Q(5,*) which indicates the fifth row of Q, and Q(*,5)
  406. which indicates the fifth column of Q.
  407. Alternatively, the third argument of COEFF can be an indeterminate,
  408. in which case nonzero coefficients are assigned to indeterminates
  409. with names constructed by concatenating the integer power, as a
  410. suffix, to the given indeterminate. For example;
  411. CLEAR C,X;
  412. COEFF(X**5+2, X, C);
  413. PAUSE;
  414. COMMENT This technique is usually more convenient when COEFF is used
  415. interactively at the top level, whereas the array technique is
  416. usually more convenient when COEFF is used indirectly within a group
  417. or block.
  418. COEFF returns the highest subscript or suffix for which it made an
  419. assignment.
  420. COEFF does not check to make sure that the coefficients do not
  421. contain its second argument within a functional form, so that is the
  422. reason we differentiated. The reason we first substituted the
  423. indeterminate !*FOO for the second argument is that differentiation
  424. does not work with respect to a functional form.
  425. The last exercise is to rewrite the last rule so that we can solve
  426. equations which simplify to the form
  427. a*x**(m+2*l) + b*x**(m+l) + c*x**m = 0, where m>=0 and l>=1.
  428. The solutions are
  429. 0, with multiplicity m,
  430. x1*E**(2*j*I*pi/l),
  431. x2*E**(2*j*I*pi/l), with j = 0, 1, ..., l-1,
  432. where x1 and x2 are the solutions to the quadratic equation
  433. a*x**2 + b*x + c = 0 .
  434. As a convenience to the user, you might also wish to have a global
  435. flag named SOLVEPRINT, such that when it is nonzero, the solutions
  436. are automatically printed.
  437. This is the end of lesson 4. When you are ready to run lesson 5,
  438. start a new REDUCE job.
  439. ;END;