NCEPLIBS-sp 2.4.0
sptranf1.f
Go to the documentation of this file.
1C> @file
2C> @brief Sptranf spectral transform.
3C> @author Iredell @date 96-02-29
4
5C> This subprogram performs an single latitude transform for
6C> subprogram sptranf(). Use this subprogram outside
7C> the sptranf() family context at your own risk.
8C>
9C> @param IROMB spectral domain shape
10C> (0 for triangular, 1 for rhomboidal)
11C> @param MAXWV spectral truncation
12C> @param IDRT grid identifier
13C> - IDRT=4 for Gaussian grid,
14C> - IDRT=0 for equally-spaced grid including poles,
15C> - IDRT=256 for equally-spaced grid excluding poles
16C> @param IMAX even number of longitudes
17C> @param JMAX number of latitudes
18C> @param JB latitude index (from pole) to begin transform
19C> @param JE latitude index (from pole) to end transform
20C> @param EPS
21C> @param EPSTOP
22C> @param ENN1
23C> @param ELONN1
24C> @param EON
25C> @param EONTOP
26C> @param CLAT cosines of latitude
27C> @param SLAT sines of latitude
28C> @param WLAT Gaussian weights
29C> @param AFFT auxiliary array if IDIR=0
30C> @param PLN Legendre polynomials
31C> @param PLNTOP Legendre polynomial over top
32C> @param MP identifier (0 for scalar, 1 for vector)
33C> @param[out] W wave field if IDIR>0
34C> @param[out] WTOP wave field over top if IDIR>0
35C> @param[out] G grid field if IDIR<0
36C> @param IDIR transform flag
37C> (IDIR>0 for wave to grid, IDIR<0 for grid to wave)
38C>
39C> @author Iredell @date 96-02-29
40 SUBROUTINE sptranf1(IROMB,MAXWV,IDRT,IMAX,JMAX,JB,JE,
41 & EPS,EPSTOP,ENN1,ELONN1,EON,EONTOP,
42 & AFFT,CLAT,SLAT,WLAT,PLN,PLNTOP,MP,
43 & W,WTOP,G,IDIR)
44
45 REAL EPS((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EPSTOP(MAXWV+1)
46 REAL ENN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
47 REAL ELONN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
48 REAL EON((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EONTOP(MAXWV+1)
49 REAL(8) AFFT(50000+4*IMAX)
50 REAL CLAT(JB:JE),SLAT(JB:JE),WLAT(JB:JE)
51 REAL PLN((MAXWV+1)*((IROMB+1)*MAXWV+2)/2,JB:JE)
52 REAL PLNTOP(MAXWV+1,JB:JE)
53 REAL W((MAXWV+1)*((IROMB+1)*MAXWV+2))
54 REAL WTOP(2*(MAXWV+1))
55 REAL G(IMAX,2,JB:JE)
56 REAL F(IMAX+2,2)
57
58 kw=(maxwv+1)*((iromb+1)*maxwv+2)
59 kwtop=2*(maxwv+1)
60 IF(idir.GT.0) THEN
61 DO j=jb,je
62 CALL spsynth(iromb,maxwv,imax,imax+2,kw,kwtop,1,
63 & clat(j),pln(1,j),plntop(1,j),mp,
64 & w,wtop,f)
65 CALL spffte(imax,(imax+2)/2,imax,2,f,g(1,1,j),+1,afft)
66 ENDDO
67 ELSE
68 DO j=jb,je
69 CALL spffte(imax,(imax+2)/2,imax,2,f,g(1,1,j),-1,afft)
70 CALL spanaly(iromb,maxwv,imax,imax+2,kw,kwtop,1,
71 & wlat(j),clat(j),pln(1,j),plntop(1,j),mp,
72 & f,w,wtop)
73 ENDDO
74 ENDIF
75
76 END
subroutine spanaly(I, M, IM, IX, NC, NCTOP, KM, WGT, CLAT, PLN, PLNTOP, MP, F, SPC, SPCTOP)
Analyzes spectral coefficients from Fourier coefficients for a latitude pair (Northern and Southern h...
Definition: spanaly.f:37
subroutine spffte(IMAX, INCW, INCG, KMAX, W, G, IDIR, AFFT)
This subprogram performs multiple fast Fourier transforms between complex amplitudes in Fourier space...
Definition: spffte.f:49
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 sptranf1(IROMB, MAXWV, IDRT, IMAX, JMAX, JB, JE, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP, AFFT, CLAT, SLAT, WLAT, PLN, PLNTOP, MP, W, WTOP, G, IDIR)
This subprogram performs an single latitude transform for subprogram sptranf().
Definition: sptranf1.f:44