34 SUBROUTINE sptranf0(IROMB,MAXWV,IDRT,IMAX,JMAX,JB,JE,
35 & EPS,EPSTOP,ENN1,ELONN1,EON,EONTOP,
36 & AFFT,CLAT,SLAT,WLAT,PLN,PLNTOP)
38 REAL EPS((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EPSTOP(MAXWV+1)
39 REAL ENN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
40 REAL ELONN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
41 REAL EON((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EONTOP(MAXWV+1)
42 REAL(8) AFFT(50000+4*IMAX)
43 REAL CLAT(JB:JE),SLAT(JB:JE),WLAT(JB:JE)
44 REAL PLN((MAXWV+1)*((IROMB+1)*MAXWV+2)/2,JB:JE)
45 REAL PLNTOP(MAXWV+1,JB:JE)
46 REAL SLATX(JMAX),WLATX(JMAX)
48 CALL spwget(iromb,maxwv,eps,epstop,enn1,elonn1,eon,eontop)
49 CALL spffte(imax,(imax+2)/2,imax,2,0.,0.,0,afft)
50 CALL splat(idrt,jmax,slatx,wlatx)
52 IF(jhe.GT.jmax/2) wlatx(jhe)=wlatx(jhe)/2
54 clat(j)=sqrt(1.-slatx(j)**2)
60 CALL splegend(iromb,maxwv,slat(j),clat(j),eps,epstop,
61 & pln(1,j),plntop(1,j))
subroutine spffte(IMAX, INCW, INCG, KMAX, W, G, IDIR, AFFT)
This subprogram performs multiple fast Fourier transforms between complex amplitudes in Fourier space...
subroutine splat(IDRT, JMAX, SLAT, WLAT)
Computes cosines of colatitude and Gaussian weights for one of the following specific global sets of ...
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 sptranf0(IROMB, MAXWV, IDRT, IMAX, JMAX, JB, JE, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP, AFFT, CLAT, SLAT, WLAT, PLN, PLNTOP)
This subprogram performs an initialization for subprogram sptranf().
subroutine spwget(IROMB, MAXWV, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP)
This subprogram gets wave-space constants.