LESS4 21 KB

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