NCEPLIBS-sp 2.4.0
sptgptv.f
Go to the documentation of this file.
1C> @file
2C> @brief Transform spectral vector to station points.
3C>
4C> ### Program History Log
5C> Date | Programmer | Comments
6C> -----|------------|---------
7C> 96-02-29 | IREDELL | Initial
8C> 1998-12-15 | IREDELL | Openmp directives inserted
9C> 1999-08-18 | IREDELL | Openmp directive typo fixed
10C> 2003-06-30 | IREDELL | use spfftpt()
11C>
12C> @author IREDELL @date 96-02-29
13
14C> This subprogram performs a spherical transform
15C> from spectral coefficients of divergences and curls
16C> to specified sets of station point vectors on the globe.
17C>
18C> The wave-space can be either triangular or rhomboidal.
19C>
20C> The wave and point fields may have general indexing,
21C> but each wave field is in sequential 'IBM order',
22C> i.e. with zonal wavenumber as the slower index.
23C>
24C> The transforms are all multiprocessed over stations.
25C>
26C> Transform several fields at a time to improve vectorization.
27C>
28C> Subprogram can be called from a multiprocessing environment.
29C>
30C> @param IROMB spectral domain shape
31c> (0 for triangular, 1 for rhomboidal)
32C> @param MAXWV spectral truncation
33C> @param KMAX number of fields to transform.
34C> @param NMAX number of station points to return
35C> @param KWSKIP skip number between wave fields
36c> (defaults to (MAXWV+1)*((IROMB+1)*MAXWV+2) IF KWSKIP=0)
37C> @param KGSKIP skip number between station point sets
38c> (defaults to NMAX IF KGSKIP=0)
39C> @param NRSKIP skip number between station lats and lons
40c> (defaults to 1 if NRSKIP=0)
41C> @param NGSKIP skip number between station points
42c> (defaults to 1 if NGSKIP=0)
43C> @param RLAT station latitudes in degrees
44C> @param RLON station longitudes in degrees
45C> @param WAVED wave divergence fields
46C> @param WAVEZ wave vorticity fields
47C> @param UP station point u-wind sets
48C> @param VP station point v-wind sets
49C>
50C> @author IREDELL @date 96-02-29
51 SUBROUTINE sptgptv(IROMB,MAXWV,KMAX,NMAX,
52 & KWSKIP,KGSKIP,NRSKIP,NGSKIP,
53 & RLAT,RLON,WAVED,WAVEZ,UP,VP)
54
55 REAL RLAT(*),RLON(*),WAVED(*),WAVEZ(*),UP(*),VP(*)
56 REAL EPS((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EPSTOP(MAXWV+1)
57 REAL ENN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
58 REAL ELONN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
59 REAL EON((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EONTOP(MAXWV+1)
60 INTEGER MP(2*KMAX)
61 REAL W((MAXWV+1)*((IROMB+1)*MAXWV+2)/2*2+1,2*KMAX)
62 REAL WTOP(2*(MAXWV+1),2*KMAX)
63 REAL PLN((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),PLNTOP(MAXWV+1)
64 REAL F(2*MAXWV+3,2,2*KMAX)
65 REAL G(2*KMAX)
66 parameter(pi=3.14159265358979)
67
68C CALCULATE PRELIMINARY CONSTANTS
69 CALL spwget(iromb,maxwv,eps,epstop,enn1,elonn1,eon,eontop)
70 mx=(maxwv+1)*((iromb+1)*maxwv+2)/2
71 mxtop=maxwv+1
72 mdim=2*mx+1
73 idim=2*maxwv+3
74 kw=kwskip
75 kg=kgskip
76 nr=nrskip
77 ng=ngskip
78 IF(kw.EQ.0) kw=2*mx
79 IF(kg.EQ.0) kg=nmax
80 IF(nr.EQ.0) nr=1
81 IF(ng.EQ.0) ng=1
82 mp=1
83
84C CALCULATE SPECTRAL WINDS
85C$OMP PARALLEL DO PRIVATE(KWS)
86 DO k=1,kmax
87 kws=(k-1)*kw
88 CALL spdz2uv(iromb,maxwv,enn1,elonn1,eon,eontop,
89 & waved(kws+1),wavez(kws+1),
90 & w(1,k),w(1,kmax+k),wtop(1,k),wtop(1,kmax+k))
91 ENDDO
92
93C CALCULATE STATION FIELDS
94C$OMP PARALLEL DO PRIVATE(KU,KV,RADLAT,SLAT1,CLAT1)
95C$OMP& PRIVATE(PLN,PLNTOP,F,G,NK)
96 DO n=1,nmax
97 radlat=pi/180*rlat((n-1)*nr+1)
98 IF(rlat((n-1)*nr+1).GE.89.9995) THEN
99 slat1=1.
100 clat1=0.
101 ELSEIF(rlat((n-1)*nr+1).LE.-89.9995) THEN
102 slat1=-1.
103 clat1=0.
104 ELSE
105 slat1=sin(radlat)
106 clat1=cos(radlat)
107 ENDIF
108 CALL splegend(iromb,maxwv,slat1,clat1,eps,epstop,
109 & pln,plntop)
110 CALL spsynth(iromb,maxwv,2*maxwv,idim,mdim,2*mxtop,2*kmax,
111 & clat1,pln,plntop,mp,w,wtop,f)
112 CALL spfftpt(maxwv,1,2*maxwv+3,1,2*kmax,rlon((n-1)*nr+1),f,g)
113 DO k=1,kmax
114 ku=k
115 kv=k+kmax
116 nk=(n-1)*ng+(k-1)*kg+1
117 up(nk)=g(ku)
118 vp(nk)=g(kv)
119 ENDDO
120 ENDDO
121
122 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
subroutine spfftpt(M, N, INCW, INCG, KMAX, RLON, W, G)
This subprogram computes a slow Fourier transform from Fourier space to a set of gridpoints.
Definition: spfftpt.f:23
subroutine splegend(I, M, SLAT, CLAT, EPS, EPSTOP, PLN, PLNTOP)
Evaluates the orthonormal associated Legendre polynomials in the spectral domain at a given latitude.
Definition: splegend.f:45
subroutine spsynth(I, M, IM, IX, NC, NCTOP, KM, CLAT, PLN, PLNTOP, MP, SPC, SPCTOP, F)
Synthesizes Fourier coefficients from spectral coefficients for a latitude pair (Northern and Souther...
Definition: spsynth.f:39
subroutine sptgptv(IROMB, MAXWV, KMAX, NMAX, KWSKIP, KGSKIP, NRSKIP, NGSKIP, RLAT, RLON, WAVED, WAVEZ, UP, VP)
This subprogram performs a spherical transform from spectral coefficients of divergences and curls to...
Definition: sptgptv.f:54
subroutine spwget(IROMB, MAXWV, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP)
This subprogram gets wave-space constants.
Definition: spwget.f:18