Document not found! Please try again

Algorithm 467: Matrix Transposition in Place - ACM Digital Library

8 downloads 0 Views 1MB Size Report
matrix in place was first proposed by Windley in 1959 [I], several algorithms have been used for its solution [2, 3, 7]. A significantly faster algorithm, based on a ...
Algorithms

L.D. Fosdick and A.K. Cline, Editors

Submittal of an algorithm for consideration for publication in Communications of the A C M implies unrestricted use of the algorithm within a computer is permissible. Copyright © 1973, Association for Computing Machinery, Inc. General permission to republish, but not for profit, all or part o f this material is granted provided that A C M ' s copyright notice is given and that reference is made to the publication, to its date o f issue, and to the fact that reprinting privileges were granted by permission of the Association for Computing Machinery.

Algorithm

procedure tqlrat (n,macheps) trans: (d, e2); value tl, macheps; integer ii; real macheps; array d, e2; comment n macheps d[l :tl] e2[l:n]

d[1 :n] e2[l:n]

Algorithm 464 Eigenvalues of a Real, Symmetric, Tridiagonal Matrix [F2] C h r i s t i a n H . R e i n s c h [ R e c d . 11 M a r . 1971] Mathematisches Institut der Technischen Universit~t, 8 0 0 0 M i i n c h e n 2, A r c i s s t r a 21, G e r m a n y

Key Words and Phrases: eigenvalues, QR Algorithm CR Categories: 5.14 Language: Algol

Description This algorithm uses a rational variant of the QR transformation with explicit shift for the computation of all of the eigenvalues of a real, symmetric, and tridiagonal matrix. Details are described in Ill. Procedures tredl or tred3 published in [2] may be used to reduce any real, symmetric matrix to tridiagonal form. Turn the matrix end-for-end if necessary to bring very large entries to the bottom right-hand corner.

begin integer i, k, m; real b, b2,f, g, h, p2, r2, s2; for i : = 2 step 1 until n do e2[i--l] : = e2[i]; e2[n] : = b : = b2 : = f : = 0.0; for k : = 1 step 1 until n do

begin h : = macheps X mac/wps X (d[k]~2 + e2[k]); if b2 < h t h e n begin b : = sqrt(h); b2 : = h end; comment Test for splitting; for m : = k step I until n do if e2[m] _< b2 then go to contl ; contl : if m = k then go to root; comment Form the shift from leading 2 X 2 block; nextit: g : = d[k]; p2 : = sqrt(e2[k]); h : = ( d [ k + l ] - - g ) / ( 2 . 0 X p 2 ) ; r2 : = sqrt(hXh+l.O); d[k] : = h : = p2/(ifh b2 then go to next#;

References 1. Reinsch, C.H. A stable, rational QR algorithm for the computation of the eigenvalues of an Hermitian, tridiagonal matrix. Math. Comp. 25 (1971), 591-597. 2. Martin, R.S., Reinseh, C.H., Wilkinson, J. H. Householder's tridiagonalization of a symmetric matrix. Numer. Math. 11 (1968), 181-195.

Input: order of the matrix, the machine precision, i.e. minimum of all x such that 1 + x > 1 on the computer, represents the diagonal of the matrix, represents the squares o f the sub-diagonal entries, (e211] is arbitrary). Output: the computed eigenvalues are stored in this array in ascending sequence, is used as working storage and the original information stored in this array is lost;

root:

h:=d[k]+f; comment One eigenvalue found, sort eigenvalues; f o r i := kstep --1 until2do if h < d[i-- 1] then d[il : = d [ i - 1] else go to coot2; i:=1; cont2: d[i] : = h

end k end tqlrat; 689

Communications of the A C M

November 1973 Volume 16 Number 11

Algorithm 465 Student's t Frequency [S 14] G.W. Hill [Recd. 24 Aug. 1971, 23 Feb. 1972, 10 July 1972] C.S.I.R.O., Division of Mathematical Statistics, Glen Osmond, South Australia

Key Words and Phrases: Student's t statistic, density function, series approximation CR Categories: 5.12, 5.5 Language: Algol

Description T h e frequency function for Student's t distribution,

r(½n + ½) f ( t in) - (~n)½r(½n~ (1 W t2/n) -(~'~+~), is evaluated for real t a n d real n > 0 to a precision near that o f the processor, even for large values of n. T h e factor involving t is evaluated as e x p ( - l ~ b ) where b is c o m p u t e d as (n W 1)In(1 W t2/n) if F / n = c is large ( > c m a x , say) or, to avoid loss of precision for smaller c, by s u m m i n g t h e series for b = (t 2 W c)(1 - c / 2 W c~/3 - c~/4 W " " ) until negligible t e r m s occur, i.e. cr/(r W 1) < ~, where ~ is the relative m a g n i t u d e of processor round-off. T h e relative error up to ~/ c m a x in evaluating hl(l W c) a n d the a c c u m u l a t e d round-off error of order E ,,/R in s u m m i n g a m a x i m u m of R t e r m s of the series c a n be limited to a b o u t the same low level by choosing c m a x = R -~ where R-½n/R "~ ~. T h u s for R = 12, 16, 23, or 32, values of c m a x ~.~ 0.2887, 0.25, 0.2085, or 0.1762, respectively, c o r r e s p o n d to processor precision where e = 2 -24, 2 -36, 2 -56, or 2 - u , respectively. Evaluation of the ratio of g a m m a functions by exponentiating the difference of almost equal values o f their logarithms would involve considerable loss of precision for large n. This is avoided by use of the asymptotic series obtained by differencing the Stirling a p p r o x i m a t i o n s , changing t h e variable to a = n - ½, a n d exponentiating the result (see also [1]): r(½n + ½)

(½a)~ ~

r(½n)

C~(4a) -~,

~=o

where Co = C~ = 1, C2 = - - 1 9 / 2 , C3 = 631/2, C4 = - 1 7 4 3 1 7 / 8 , C~ = 204 91783/8, C6 = - 7 3 3 4 8 01895/16, C7 = 185 85901 54455/16, Cs = - 5 06774 10817 68765/128, C9 = 2236 25929 81667 88235/128, C10 = - 2 4 80926 53157 85763 70237/256. T h e relative error of t h e s u m of the first s terms is negligible for n > nmin where I c~ I × [4 ( n m i n - ½)]-2, ~ ~, e.g. for s = 5 a n d ~ = 2 -24 or 2 -3~, nmin ~ 6.271 or 13.76, respectively, a n d for s = 10 a n d ~ = 2 - ~ or 2 -~, nmht ~ 15.5 or 40.89, respectively. For smaller n the ratio of g a m m a functions is obtained f r o m the ratio for s o m e N >_ nmin by the relation: r(½n W ½)

r(½n)

n

(n q- 2)

(n W 1) (n + 3)

(N - 2) r(½N W ½)

(N-- 1) r(1N)

F o r large n, processor u n d e r t o w at line 21 is avoided by use of the n o r m a l a p p r o x i m a t i o n , which is adequate for values of n > 1/~, whose representation is unaffected by subtraction o f 0.5. Protection against negative or zero n is provided by returning the distinctive value, - 1 . 0 , which m a y be s u p p l e m e n t e d by a n error diagnostic process, if required. For double precision calculations speed is improved by evaluating higher order t e r m s o f the g a m m a ratio series using single precision operations. C o m p a r i s o n o f double precision (~ = 2 -84)

690

results with single precision results (e = 2 -36, nmin = 13.76, c m a x = 0.25) for a Control D a t a 3200 indicated achievement generally o f a b o u t ten significant decimal digits, dropping to a b o u t eight significant decimals for a r g u m e n t s b e y o n d the 10-~0 probability level. Valuable c o m m e n t s f r o m the referee are gratefully acknowledged.

Reference 1. Fields, J.L. A note on the asymptotic expansion of a ratio o f G a m m a functions. Proc. Edinburgh Math. Soc. Ser. 2 15 (1966), 43-45.

Algorithm real procedure t frequency (t, n); value t, n; real t, n; if n _< 0.0 then t frequency : = - - 1 . 0 else begin real a, b, c, d, e, nmin, cmax; comment for 36-bit precision processor; nmin := 13.76; c m a x : = 0.25; b : = t >( t ; c : = b / n ; a := d : = b W c ; if c > c m a x then b : = (nW1.0) X h1(1.0-t-c)

else for e : = 2.0, e W 1.0 while b ~ d d o begin a : = - - a )< c; b : = d; d : = a / e W d end; a : = n; c : = 0.3989422804; comment 1/sqrt(2r) = 0.3989422804014326779399461 . . . ; for e : = a while e < nrn'in do begin e : = c X a / ( a W l . O ) ; a : = a W 2.0 end; a : = a -- 0.5;

if a ~ n then begin c : = sqrt(a/n) X c; a : = 0.25/a; a : = a )< a; c := ((((-21789.625XaW315.5) Xa-9.5) XaW1.0) XaW1.0) ×c

end; t frequency := e x p ( - O . 5 X b )

X c

end Student's t-frequency

Algorithm 466 Four Combinatorial Algorithms [G6] Gideon Ehrlich [Recd. 25 Aug. 1971, 4 Jan. 1972, and 12 Dec. 1972] Department of Applied Mathematics, Weizmann Institute of Science, Rehovot, Israel Key Words and Phrases: permutations and combinations CR Categories: 5.39 Language: PL/I Description Each o f the following algorithms produce, by successive calls, a sequence of all combinatorial configurations, belonging to the appropriate type. PERMU P e r m u t a t i o n s of N>_3 objects: X(1), X ( 2 ) , . . . , X(N). C O M B I C o m b i n a t i o n s of M natural n u m b e r s o u t of the first N. COMPOMIN C o m p o s i t i o n s of a n integer P to M W 1 ordered terms, I N D E X ( k ) , each of which is not less t h a n a given minimum MIN(k). Communications of the A C M

N o v e m b e r 1973 Volume 16 N u m b e r 11

C O M P O M A X The same as C O M P O M I N but each term has its own maximum M A X (k). The four algorithms have in common the important property that they use neither loops nor recursion; thus the time needed for producing a new configuration is unaffected by the "size" (N, N and M, P and M respectively) of that configuration. Each algorithm uses a single simple operation for producing a new configuration from the old one, that is: P E R M U A single transposition of two adjacent elements. COMBI Replacing a single element x by a y having the property that there is no element between x and y belonging to the combination. C O M P O M I N ( M A X ) Changing the values of two adjacent terms (usually only by 1). The algorithms are written in PL1 (F). Special instructions for the user and notes. P E R M U (1) The mean work-time is actually a decreasing function of N since, on (N -- 1)/N of the calls, it returns by the first RETURN. (2) The procedure operates directly on any object vector x[l:N]. (3) For the first permutation one must call FIRSTPER; for other permutations P E R M U must be used. (4) Together with the last permutation, which is the original one, we will get D O N E = 'I'B. If we continue to call P E R M U , the entire sequence will repeat indefinitely. If at any stage we set D O N E = 'O'B, then at the end of the appropriate sequence it will become 'I'B. (5) The entire resulting sequence is the same as that of Johnson [1] and Trotter [2]. C O M B I Every combination is represented in two forms: (1) As a bit array of M ' l ' s and N -- M 'O's which is identical to A(1), A ( 2 ) , . . . , A(N). (2) As an array C of M different integers not greater than N. The M elements are ordered according to their magnitude. If the second representation is not needed one can omit Z, H and C together with the last line of the procedure. For the first combination we can use the following initialization (for other initializations see [3]): D E C L A R E A(O:N) B I T (1), (X, Y, T(N), F(0:N), I, L, Z, H(N), C(M)) FIXED; DO K = 0 TO N -- M; A(K) = '0~B; END; DO K = N - - M + 1 TO N; A(K) = ' I ' B ; E N D ; DO K = 1 TO M; C(K) = N - - M - F K; H ( N - - M - F K) = K; END; T ( N - M) = - 1 ; T(1) = 0; F(N) = N - - M-}- 1 ; I = N - M; L = N; (The initialization was not done in the body of the procedure COMBI only in order to simplify the procedures C O M P O M I N MAX:.) Instead of using such a large number of parameters it is possible to retain only A, I, L as parameters of the procedure and declare and initialize the other present parameters in the body of the procedure (as is done in PERMU). In such a case N, T, F, L, H must be declared as S T A T I C or CONTROLLED ('own' in ALGOL). C O M P O M I N Each of the M + 1 MIN(k), as well as P, can be any integer (positive, negative, or zero), but the sum S of all those minima cannot be greater than P. For the first composition set INDEX(I) = P - S + MIN(I) INDEX(k) = MIN(k), for k > 1. Set N = P - S + M, and declare and initialize all variables that also appear in COMBI in the same way as was done for COMBI. Together with the last composition, we will get I = 0 as a signal to halt. C O M P O M A X The instructions for C O M P O M I N are valid for C O M P O M A X provided: (1) M I N is replaced by M A X (S > P); and (2) N is initialized to N = S - P -t- M. The vector C (but not H!) has no use in COMPOMIN(M,4X), so one can omit all statements in which it appears. A justification for the four algorithms and for some others can be found in [3].

References 1. Johnson, S.N. Generation of permutations by adjacent transformations. Math. Comp. 17 (1963), 282-285. 2. Trotter, H.F. Algorithm 115, Perm. Comm A C M 5 (Aug. 1962), pp. 434-435. 3. Ehrlicb, G., Loopless algorithms for generation permutations combinations and other combinatorial configurations. J. A C M 20 (July 1973), 500-513.

Algorithm FIRSTPER: PROCEDURE (X,DONE); DECLARE (X(*), (XN,XX) STATIC) DECIMAL, DONEBIT(1) (N,S,V,M,LjI,DI,IPI) BINARYSTATIC, (p(O:N),IP(N-I~D(N-I),T(N)) BINARYCONTROLLED; N=OIM(X,I); IF ALLOCATION(P) THENFREEP,IP,D,T; ALLOCATEP,IP,D,T; DOM=l TO N-l; P(M),IP(M)=M; D(M)=-]; END; XN=X(N); V=-I; S,P(O),P(N)=N; M,L=I; T(N)=N-I; T(N-I)=-2; T(2)=2; DONE='O'B; PERMU: ENTRY (X,DONE); IF S.=M THENDO; X(S)=X(S+V); S=S+V; X(S)=XN; RETURN;END; I=T(N); DI=D(1); IP(1),IPI=IP(1)+DI; M=P(IPI); IP(M)=IPI-OI; P(IPI-DI)=M; P(IPI)=I; M=IPI+L; XX=X(M); X(M)=X(M-OI); X(M-DI)=XX; L=I-L; V=-V; M=N+I-S; IF P(IPI+DI) < I THEN DO; IF I=N-l THENRETURN; T(N)=N-I; T(N-I) = -I; RETURN; END; D(1)=-DI; IF T(1) < 0 THEN DO; IF T(1)-~=l-I THENT(I-I)=T(1); T(1)=I-l; END; IF I ~ = N - l THENDO; T(N)=N-I; T(N-l)=-I-l; END; T(I+I)=T(1); IF I=2 & P(2)=2 THENDONE=')'B; END; COMBI PROCEDURE (A,N,X,Y,T,F,I,L,Z,H,C); DECLARE A(*)BIT(1), (N,X,Y,T(*),F(*),I,L,Z,H(*),C(*)) FIXED; IF T(1) < 0 THEN DO; IF-T(I)"~=I-] THEN T(I-I)=T(I); T(1)=I-]; END; IF--, A(1) THEN DO; X=I; Y=F(L); IF A(I-7) THEN F(I)=F(I-I); ELSEF(I)=I; IF F(L)=L THEN DO; L=I; I=T(1); GOTOCHANGE;END; IF L=N THEN DO; T(F(N))=-I-]; T(I+I)=T(1); I=F(N); F(N)=F(N)+I; GOTOCHANGE; END; T(L)=-I-I; T(I+])=T(1); F(L)=F(L)+~; I=L; GOTOCHANGE END; Y=I; IF I-I=L THEN DO; F(L),X:F(L)-I; F(I-I)=P(1); IF L=N THEN DO; IF I=F(N) -l THENDO; I=T(1); GOTOCHANGE;END; T(F(N)-])=-I-I; T(I+I)=T(1); I=F(N)-l; GOTOCHANGE; END; T(L)=-I-I; T(I+I)=T(I); I=L; GOTOCHANGE; END; X=N; F(L-I)=F(L); F(N)=N; L=N; IF I=N-I THENDO; I=T(N-]); GOTOCHANGE;END; T(N-I)=-I-I; T(I+I)=T(1); I=N-l; CHANGE; A(X)='I'B; A(y)='O'B; H(X),Z=H(Y); C(Z)=X; END COMBI; COMPOMIN: PROCEDURE(INDEX,A,N,X,Y,T,F,I,L,Z,H,C); DECLAREA(*) BIT(1), (INDEX(*),N,X,Y,T (*),F(*),I,L,Z,H(*),C(*)) FIXED; CALL COMBI (A,N,X,Y,T,F,I,L,Z,H,C); INDEX(Z)=INDEX(Z)+X-Y; INDEX(Z+I)=INDEX(Z+I)~Y-X: END COMPOMIN; COMPOMAX:PROCEDURE(INDEX,A,N,X.Y,T,F.I,L,Z.H,C); DECLAREA(*) BIT(1), (INDEX(*),N,X,Y,T(*),F(*),I,L,Z,H(*),C(*)) FIXED; CALL COMBI (A,N,X,Y,T,F,I,L,Z.H,C); INOEX(Z)=INDEX(Z)-X+y; INDEX(Z+I)=INDEX(Z+]).y+x; END COMPOMAX;

Acknowledgment. I would like to thank Professor Shimon Even for guidance and encouragement. 691

Communications of the ACM

November 1973 Volume 16 Number 11

Algorithm 467

Pr~oor. Both m and s are divisible by d, and therefore so is any subcycle element sn r (mod m). But n and m have no common factors (since m = nn2 - 1), so no divisor of m larger than d can divide sn r. [] THEOREM 2. For every subcycle beginning with s, there is

Matrix Transposition in Place [F 1]

another (possibly the same) subcycle beginning with m -

N o r m a n B r e n n e r [ R e c d . 14 F e b . 1972, 2 A u g . 1972] M.I.T., Department of Earth and Planetary Sciences, Cambridge, MA 02139

Let ri be a primitive root o f pi ; that is, the powers ri k (mod Pi) f o r k = 0, 1 , . . . , p - 2, comprise every positive integer less than Pi • Define the generator gl = 1 -b R m / p i etl , where R =-- (ri -- 1)

Key Words and Phrases: transposition, matrix operations, permutations, primitive roots, number theory CR Categories: 3.15, 5.14, 5.39 Language: Fortran

(m/p~. i) -1 (mod p~. i). Define the Euler totient function 4~(1) = 1; otherwise 4~(k) = the number o f integers less than k having no common factor with it. Then, f o r any integer x less than m, there exist unique indices ji f o r which 0