53 SUBROUTINE sptgpm(IROMB,MAXWV,KMAX,MI,MJ,
54 & KWSKIP,KGSKIP,NISKIP,NJSKIP,
55 & RLAT1,RLON1,DLAT,DLON,WAVE,GM)
58 REAL EPS((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EPSTOP(MAXWV+1)
59 REAL ENN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
60 REAL ELONN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
61 REAL EON((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EONTOP(MAXWV+1)
63 REAL WTOP(2*(MAXWV+1),KMAX)
64 REAL PLN((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),PLNTOP(MAXWV+1)
65 REAL F(2*MAXWV+3,2,KMAX)
66 REAL CLAT(MJ),SLAT(MJ),CLON(MAXWV,MI),SLON(MAXWV,MI)
67 parameter(rerth=6.3712e6)
68 parameter(pi=3.14159265358979,dpr=180./pi)
71 CALL spwget(iromb,maxwv,eps,epstop,enn1,elonn1,eon,eontop)
72 mx=(maxwv+1)*((iromb+1)*maxwv+2)/2
84 rlon=mod(rlon1+dlon*(i-1)+3600,360.)
86 clon(l,i)=cos(l*rlon/dpr)
87 slon(l,i)=sin(l*rlon/dpr)
90 ye=1-log(tan((rlat1+90)/2/dpr))*dpr/dlat
92 rlat=atan(exp(dlat/dpr*(j-ye)))*2*dpr-90
105 CALL splegend(iromb,maxwv,slat(j),clat(j),eps,epstop,
107 CALL spsynth(iromb,maxwv,2*maxwv,idim,kw,2*mxtop,kmax,
108 & clat(j),pln,plntop,mp,wave,wtop,f)
111 ijk=(i-1)*ni+(j-1)*nj+(k-1)*kg+1
116 ijk=(i-1)*ni+(j-1)*nj+(k-1)*kg+1
117 gm(ijk)=gm(ijk)+2.*(f(2*l+1,1,k)*clon(l,i)
118 & -f(2*l+2,1,k)*slon(l,i))
subroutine splegend(I, M, SLAT, CLAT, EPS, EPSTOP, PLN, PLNTOP)
Evaluates the orthonormal associated Legendre polynomials in the spectral domain at a given latitude.
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...
subroutine sptgpm(IROMB, MAXWV, KMAX, MI, MJ, KWSKIP, KGSKIP, NISKIP, NJSKIP, RLAT1, RLON1, DLAT, DLON, WAVE, GM)
This subprogram performs a spherical transform from spectral coefficients of scalar quantities to sca...
subroutine spwget(IROMB, MAXWV, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP)
This subprogram gets wave-space constants.