NCEPLIBS-sp  2.3.3
spdz2uv.f
Go to the documentation of this file.
1 C> @file
2 C
3 C> Compute winds from divergence and vorticity
4 C> @author IREDELL ORG: W/NMC23 @date 92-10-31
5 
6 C> Computes the wind components from divergence and vorticity
7 c> in spectral space.
8 C> Subprogram speps should be called already.
9 C> If L is the zonal wavenumber, N is the total wavenumber,
10 C> <pre>
11 C> EPS(L,N) = SQRT((N**2-L**2)/(4*N**2-1))
12 C> </pre>
13 C> and A is earth radius,
14 C> then the zonal wind component U is computed as
15 C> <pre>
16 C> U(L,N)=-I*L/(N*(N+1))*A*D(L,N)
17 C> +EPS(L,N+1)/(N+1)*A*Z(L,N+1)-EPS(L,N)/N*A*Z(L,N-1)
18 C> </pre>
19 C> and the meridional wind component V is computed as
20 C> <pre>
21 C> V(L,N)=-I*L/(N*(N+1))*A*Z(L,N)
22 C> -EPS(L,N+1)/(N+1)*A*D(L,N+1)+EPS(L,N)/N*A*D(L,N-1)
23 C> </pre>
24 C> where D is divergence and Z is vorticity.
25 C> U and V are weighted by the cosine of latitude.
26 C> Cxtra terms are computed over top of the spectral domain.
27 C> Advantage is taken of the fact that EPS(L,L)=0
28 C> in order to vectorize over the entire spectral domain.
29 C>
30 C> @param I - INTEGER SPECTRAL DOMAIN SHAPE
31 C> (0 FOR TRIANGULAR, 1 FOR RHOMBOIDAL)
32 C> @param M - INTEGER SPECTRAL TRUNCATION
33 C> @param ENN1 - REAL ((M+1)*((I+1)*M+2)/2) N*(N+1)/A**2
34 C> @param ELONN1 - REAL ((M+1)*((I+1)*M+2)/2) L/(N*(N+1))*A
35 C> @param EON - REAL ((M+1)*((I+1)*M+2)/2) EPSILON/N*A
36 C> @param EONTOP - REAL (M+1) EPSILON/N*A OVER TOP
37 C> @param D - REAL ((M+1)*((I+1)*M+2)) DIVERGENCE
38 C> @param Z - REAL ((M+1)*((I+1)*M+2)) VORTICITY
39 C> @param U - REAL ((M+1)*((I+1)*M+2)) ZONAL WIND (TIMES COSLAT)
40 C> @param V - REAL ((M+1)*((I+1)*M+2)) MERID WIND (TIMES COSLAT)
41 C> @param UTOP - REAL (2*(M+1)) ZONAL WIND (TIMES COSLAT) OVER TOP
42 C> @param VTOP - REAL (2*(M+1)) MERID WIND (TIMES COSLAT) OVER TOP
43 C>
44  SUBROUTINE spdz2uv(I,M,ENN1,ELONN1,EON,EONTOP,D,Z,U,V,UTOP,VTOP)
45  REAL ENN1((M+1)*((I+1)*M+2)/2),ELONN1((M+1)*((I+1)*M+2)/2)
46  REAL EON((M+1)*((I+1)*M+2)/2),EONTOP(M+1)
47  REAL D((M+1)*((I+1)*M+2)),Z((M+1)*((I+1)*M+2))
48  REAL U((M+1)*((I+1)*M+2)),V((M+1)*((I+1)*M+2))
49  REAL UTOP(2*(M+1)),VTOP(2*(M+1))
50 C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
51 C COMPUTE WINDS IN THE SPECTRAL DOMAIN
52  k=1
53  u(2*k-1)=eon(k+1)*z(2*k+1)
54  u(2*k)=eon(k+1)*z(2*k+2)
55  v(2*k-1)=-eon(k+1)*d(2*k+1)
56  v(2*k)=-eon(k+1)*d(2*k+2)
57  DO k=2,(m+1)*((i+1)*m+2)/2-1
58  u(2*k-1)=elonn1(k)*d(2*k)+eon(k+1)*z(2*k+1)-eon(k)*z(2*k-3)
59  u(2*k)=-elonn1(k)*d(2*k-1)+eon(k+1)*z(2*k+2)-eon(k)*z(2*k-2)
60  v(2*k-1)=elonn1(k)*z(2*k)-eon(k+1)*d(2*k+1)+eon(k)*d(2*k-3)
61  v(2*k)=-elonn1(k)*z(2*k-1)-eon(k+1)*d(2*k+2)+eon(k)*d(2*k-2)
62  ENDDO
63  k=(m+1)*((i+1)*m+2)/2
64  u(2*k-1)=elonn1(k)*d(2*k)-eon(k)*z(2*k-3)
65  u(2*k)=-elonn1(k)*d(2*k-1)-eon(k)*z(2*k-2)
66  v(2*k-1)=elonn1(k)*z(2*k)+eon(k)*d(2*k-3)
67  v(2*k)=-elonn1(k)*z(2*k-1)+eon(k)*d(2*k-2)
68 C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
69 C COMPUTE WINDS OVER TOP OF THE SPECTRAL DOMAIN
70  DO l=0,m
71  k=l*(2*m+(i-1)*(l-1))/2+i*l+m+1
72  utop(2*l+1)=-eontop(l+1)*z(2*k-1)
73  utop(2*l+2)=-eontop(l+1)*z(2*k)
74  vtop(2*l+1)=eontop(l+1)*d(2*k-1)
75  vtop(2*l+2)=eontop(l+1)*d(2*k)
76  ENDDO
77 C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
78  RETURN
79  END
spdz2uv
subroutine spdz2uv(I, M, ENN1, ELONN1, EON, EONTOP, D, Z, U, V, UTOP, VTOP)
Compute winds from divergence and vorticity.
Definition: spdz2uv.f:45