NCEPLIBS-sp  2.3.3
speps.f
Go to the documentation of this file.
1 C>@file
2 C>
3 C> Compute utility spectral fields
4 C> @author IREDELL @date 92-10-31
5 
6 C> Computes constant fields indexed in the spectral domain
7 C> in "IBM ORDER" (Zonal wavenumber is the slower index).
8 C> If L is the zonal wavenumber and N is the total wavenumber
9 C> and A is the earth radius, then the fields returned are:
10 C> - (1) NORMALIZING FACTOR EPSILON=SQRT((N**2-L**2)/(4*N**2-1))
11 C> - (2) LAPLACIAN FACTOR N*(N+1)/A**2
12 C> - (3) ZONAL DERIVATIVE/LAPLACIAN FACTOR L/(N*(N+1))*A
13 C> - (4) MERIDIONAL DERIVATIVE/LAPLACIAN FACTOR EPSILON/N*A
14 C>
15 C> @param I - INTEGER SPECTRAL DOMAIN SHAPE
16 C> (0 FOR TRIANGULAR, 1 FOR RHOMBOIDAL)
17 C> @param M - INTEGER SPECTRAL TRUNCATION
18 C> @param EPS - REAL ((M+1)*((I+1)*M+2)/2) SQRT((N**2-L**2)/(4*N**2-1))
19 C> @param EPSTOP - REAL (M+1) SQRT((N**2-L**2)/(4*N**2-1)) OVER TOP
20 C> @param ENN1 - REAL ((M+1)*((I+1)*M+2)/2) N*(N+1)/A**2
21 C> @param ELONN1 - REAL ((M+1)*((I+1)*M+2)/2) L/(N*(N+1))*A
22 C> @param EON - REAL ((M+1)*((I+1)*M+2)/2) EPSILON/N*A
23 C> @param EONTOP - REAL (M+1) EPSILON/N*A OVER TOP
24 C>
25  SUBROUTINE speps(I,M,EPS,EPSTOP,ENN1,ELONN1,EON,EONTOP)
26  REAL EPS((M+1)*((I+1)*M+2)/2),EPSTOP(M+1)
27  REAL ENN1((M+1)*((I+1)*M+2)/2),ELONN1((M+1)*((I+1)*M+2)/2)
28  REAL EON((M+1)*((I+1)*M+2)/2),EONTOP(M+1)
29  parameter(rerth=6.3712e6,ra2=1./rerth**2)
30 C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
31  DO l=0,m
32  k=l*(2*m+(i-1)*(l-1))/2+l+1
33  eps(k)=0.
34  enn1(k)=ra2*l*(l+1)
35  elonn1(k)=rerth/(l+1)
36  eon(k)=0.
37  ENDDO
38  DO l=0,m
39  DO n=l+1,i*l+m
40  k=l*(2*m+(i-1)*(l-1))/2+n+1
41  eps(k)=sqrt(float(n**2-l**2)/float(4*n**2-1))
42  enn1(k)=ra2*n*(n+1)
43  elonn1(k)=rerth*l/(n*(n+1))
44  eon(k)=rerth/n*eps(k)
45  ENDDO
46  ENDDO
47  DO l=0,m
48  n=i*l+m+1
49  epstop(l+1)=sqrt(float(n**2-l**2)/float(4*n**2-1))
50  eontop(l+1)=rerth/n*epstop(l+1)
51  ENDDO
52 C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
53  RETURN
54  END
speps
subroutine speps(I, M, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP)
Computes constant fields indexed in the spectral domain in "IBM ORDER" (Zonal wavenumber is the slowe...
Definition: speps.f:26