NCEPLIBS-sp  2.5.0
sptgpt.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Transform spectral scalar to station points.
3 C>
4 C> ### Program History Log
5 C> Date | Programmer | Comments
6 C> -----|------------|---------
7 C> 96-02-29 | Iredell | Initial.
8 C> 1998-12-15 | Iredell | Openmp directives inserted.
9 C> 2003-06-30 | Iredell | Use spfftpt().
10 C>
11 C> @author Iredell @date 96-02-29
12 
13 C> This subprogram performs a spherical transform
14 c> from spectral coefficients of scalar quantities
15 c> to specified sets of station points on the globe.
16 C>
17 C> The wave-space can be either triangular or rhomboidal.
18 C>
19 C> The wave and point fields may have general indexing,
20 c> but each wave field is in sequential 'IBM order',
21 c> i.e. with zonal wavenumber as the slower index.
22 C>
23 C> The transforms are all multiprocessed over stations.
24 C>
25 C> Transform several fields at a time to improve vectorization.
26 C>
27 C> Subprogram can be called from a multiprocessing environment.
28 C>
29 C> @param IROMB spectral domain shape
30 C> (0 for triangular, 1 for rhomboidal)
31 C> @param MAXWV spectral truncation
32 C> @param KMAX number of fields to transform.
33 C> @param NMAX number of station points to return
34 C> @param KWSKIP skip number between wave fields
35 C> (defaults to (MAXWV+1)*((IROMB+1)*MAXWV+2) if KWSKIP=0)
36 C> @param KGSKIP skip number between station point sets
37 C> (defaults to NMAX if KGSKIP=0)
38 C> @param NRSKIP skip number between station lats and lons
39 C> (defaults to 1 if NRSKIP=0)
40 C> @param NGSKIP skip number between station points
41 C> (defaults to 1 if NGSKIP=0)
42 C> @param RLAT station latitudes in degrees
43 C> @param RLON station longitudes in degrees
44 C> @param WAVE wave fields
45 C> @param GP station point sets
46 C>
47 C> @author Iredell @date 96-02-29
48  SUBROUTINE sptgpt(IROMB,MAXWV,KMAX,NMAX,
49  & KWSKIP,KGSKIP,NRSKIP,NGSKIP,
50  & RLAT,RLON,WAVE,GP)
51 
52  REAL RLAT(*),RLON(*),WAVE(*),GP(*)
53  REAL EPS((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EPSTOP(MAXWV+1)
54  REAL ENN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
55  REAL ELONN1((MAXWV+1)*((IROMB+1)*MAXWV+2)/2)
56  REAL EON((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),EONTOP(MAXWV+1)
57  INTEGER MP(KMAX)
58  REAL WTOP(2*(MAXWV+1),KMAX)
59  REAL PLN((MAXWV+1)*((IROMB+1)*MAXWV+2)/2),PLNTOP(MAXWV+1)
60  REAL F(2*MAXWV+3,2,KMAX)
61  parameter(pi=3.14159265358979)
62 
63 C CALCULATE PRELIMINARY CONSTANTS
64  CALL spwget(iromb,maxwv,eps,epstop,enn1,elonn1,eon,eontop)
65  mx=(maxwv+1)*((iromb+1)*maxwv+2)/2
66  mxtop=maxwv+1
67  idim=2*maxwv+3
68  kw=kwskip
69  kg=kgskip
70  nr=nrskip
71  ng=ngskip
72  IF(kw.EQ.0) kw=2*mx
73  IF(kg.EQ.0) kg=nmax
74  IF(nr.EQ.0) nr=1
75  IF(ng.EQ.0) ng=1
76  mp=0
77 C$OMP PARALLEL DO
78  DO k=1,kmax
79  wtop(1:2*mxtop,k)=0
80  ENDDO
81 
82 C CALCULATE STATION FIELDS
83 C$OMP PARALLEL DO PRIVATE(RADLAT,SLAT1,CLAT1)
84 C$OMP& PRIVATE(PLN,PLNTOP,F,NK)
85  DO n=1,nmax
86  radlat=pi/180*rlat((n-1)*nr+1)
87  IF(rlat((n-1)*nr+1).GE.89.9995) THEN
88  slat1=1.
89  clat1=0.
90  ELSEIF(rlat((n-1)*nr+1).LE.-89.9995) THEN
91  slat1=-1.
92  clat1=0.
93  ELSE
94  slat1=sin(radlat)
95  clat1=cos(radlat)
96  ENDIF
97  CALL splegend(iromb,maxwv,slat1,clat1,eps,epstop,
98  & pln,plntop)
99  CALL spsynth(iromb,maxwv,2*maxwv,idim,kw,2*mxtop,kmax,
100  & clat1,pln,plntop,mp,wave,wtop,f)
101  CALL spfftpt(maxwv,1,2*maxwv+3,kg,kmax,rlon((n-1)*nr+1),
102  & f,gp((n-1)*ng+1))
103  ENDDO
104  END
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 sptgpt(IROMB, MAXWV, KMAX, NMAX, KWSKIP, KGSKIP, NRSKIP, NGSKIP, RLAT, RLON, WAVE, GP)
This subprogram performs a spherical transform from spectral coefficients of scalar quantities to spe...
Definition: sptgpt.f:51
subroutine spwget(IROMB, MAXWV, EPS, EPSTOP, ENN1, ELONN1, EON, EONTOP)
This subprogram gets wave-space constants.
Definition: spwget.f:18