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