NCEPLIBS-ip  5.1.0
ip_lambert_conf_grid_mod.F90
Go to the documentation of this file.
1 
5 
16  use ip_grid_mod
19  implicit none
20 
21  private
22  public :: ip_lambert_conf_grid
23 
24  type, extends(ip_grid) :: ip_lambert_conf_grid
25  real :: rlat1
26  real :: rlon1
27  real :: rlati1
28  real :: rlati2
29  real :: orient
30  real :: dxs
31  real :: dys
32  real :: h
33  integer :: irot
34  contains
36  procedure :: init_grib1
38  procedure :: init_grib2
41  procedure :: gdswzd => gdswzd_lambert_conf
42  end type ip_lambert_conf_grid
43 
44  INTEGER :: irot
45  REAL :: an
46  REAL :: dxs
47  REAL :: dys
48  REAL :: h
49  REAL :: rerth
50  REAL :: tinyreal=tiny(1.0)
51 
52 contains
53 
60  subroutine init_grib1(self, g1_desc)
61  class(ip_lambert_conf_grid), intent(inout) :: self
62  type(grib1_descriptor), intent(in) :: g1_desc
63 
64  real :: dx, dy, hi, hj
65  integer :: iproj, iscan, jscan
66 
67  associate(kgds => g1_desc%gds)
68  self%rerth = 6.3712e6
69  self%eccen_squared = 0.0
70 
71  self%IM=kgds(2)
72  self%JM=kgds(3)
73 
74  self%RLAT1=kgds(4)*1.e-3
75  self%RLON1=kgds(5)*1.e-3
76 
77  self%IROT=mod(kgds(6)/8,2)
78  self%ORIENT=kgds(7)*1.e-3
79 
80  dx=kgds(8)
81  dy=kgds(9)
82 
83  iproj=mod(kgds(10)/128,2)
84  iscan=mod(kgds(11)/128,2)
85  jscan=mod(kgds(11)/64,2)
86 
87  self%RLATI1=kgds(12)*1.e-3
88  self%RLATI2=kgds(13)*1.e-3
89  self%H=(-1.)**iproj
90 
91  hi=(-1.)**iscan
92  hj=(-1.)**(1-jscan)
93  self%DXS=dx*hi
94  self%DYS=dy*hj
95 
96  self%iwrap = 0
97  self%jwrap1 = 0
98  self%jwrap2 = 0
99  self%nscan = mod(kgds(11) / 32, 2)
100  self%nscan_field_pos = self%nscan
101  self%kscan = 0
102  end associate
103 
104  end subroutine init_grib1
105 
112  subroutine init_grib2(self, g2_desc)
113  class(ip_lambert_conf_grid), intent(inout) :: self
114  type(grib2_descriptor), intent(in) :: g2_desc
115 
116  real :: dx, dy, hi, hj
117  integer :: iproj, iscan, jscan
118 
119 
120  associate(igdtmpl => g2_desc%gdt_tmpl, igdtlen => g2_desc%gdt_len)
121  call earth_radius(igdtmpl, igdtlen, self%rerth, self%eccen_squared)
122 
123  self%IM=igdtmpl(8)
124  self%JM=igdtmpl(9)
125 
126  self%RLAT1=float(igdtmpl(10))*1.0e-6
127  self%RLON1=float(igdtmpl(11))*1.0e-6
128 
129  self%IROT=mod(igdtmpl(12)/8,2)
130  self%ORIENT=float(igdtmpl(14))*1.0e-6
131 
132  dx=float(igdtmpl(15))*1.0e-3
133  dy=float(igdtmpl(16))*1.0e-3
134 
135  iproj=mod(igdtmpl(17)/128,2)
136  iscan=mod(igdtmpl(18)/128,2)
137  jscan=mod(igdtmpl(18)/64,2)
138 
139  self%RLATI1=float(igdtmpl(19))*1.0e-6
140  self%RLATI2=float(igdtmpl(20))*1.0e-6
141 
142  self%H=(-1.)**iproj
143  hi=(-1.)**iscan
144  hj=(-1.)**(1-jscan)
145  self%DXS=dx*hi
146  self%DYS=dy*hj
147 
148  self%nscan = mod(igdtmpl(18) / 32, 2)
149  self%nscan_field_pos = self%nscan
150  self%iwrap = 0
151  self%jwrap1 = 0
152  self%jwrap2 = 0
153  self%kscan = 0
154  end associate
155  end subroutine init_grib2
156 
219  SUBROUTINE gdswzd_lambert_conf(self,IOPT,NPTS,FILL, &
220  XPTS,YPTS,RLON,RLAT,NRET, &
221  CROT,SROT,XLON,XLAT,YLON,YLAT,AREA)
222  IMPLICIT NONE
223  !
224  class(ip_lambert_conf_grid), intent(in) :: self
225  INTEGER, INTENT(IN ) :: IOPT, NPTS
226  INTEGER, INTENT( OUT) :: NRET
227  !
228  REAL, INTENT(IN ) :: FILL
229  REAL, INTENT(INOUT) :: RLON(NPTS),RLAT(NPTS)
230  REAL, INTENT(INOUT) :: XPTS(NPTS),YPTS(NPTS)
231  REAL, OPTIONAL, INTENT( OUT) :: CROT(NPTS),SROT(NPTS)
232  REAL, OPTIONAL, INTENT( OUT) :: XLON(NPTS),XLAT(NPTS)
233  REAL, OPTIONAL, INTENT( OUT) :: YLON(NPTS),YLAT(NPTS),AREA(NPTS)
234  !
235  INTEGER :: IM, JM, N
236  !
237  LOGICAL :: LROT, LMAP, LAREA
238  !
239  REAL :: ANTR, DI, DJ
240  REAL :: DLON1
241  REAL :: DE, DE2, DR2
242  REAL :: ORIENT, RLAT1, RLON1
243  REAL :: RLATI1, RLATI2
244  REAL :: XMAX, XMIN, YMAX, YMIN, XP, YP
245  REAL :: DLON, DR
246  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
247  IF(PRESENT(crot)) crot=fill
248  IF(PRESENT(srot)) srot=fill
249  IF(PRESENT(xlon)) xlon=fill
250  IF(PRESENT(xlat)) xlat=fill
251  IF(PRESENT(ylon)) ylon=fill
252  IF(PRESENT(ylat)) ylat=fill
253  IF(PRESENT(area)) area=fill
254 
255  im=self%im
256  jm=self%jm
257 
258  rlat1=self%rlat1
259  rlon1=self%rlon1
260 
261  irot=self%irot
262  orient=self%orient
263 
264  rlati1=self%rlati1
265  rlati2=self%rlati2
266 
267  h=self%h
268  dxs=self%dxs
269  dys=self%dys
270 
271  rerth = self%rerth
272 
273  IF(abs(rlati1-rlati2).LT.tinyreal) THEN
274  an=sin(rlati1/dpr)
275  ELSE
276  an=log(cos(rlati1/dpr)/cos(rlati2/dpr))/ &
277  log(tan((90-rlati1)/2/dpr)/tan((90-rlati2)/2/dpr))
278  ENDIF
279  de=rerth*cos(rlati1/dpr)*tan((rlati1+90)/2/dpr)**an/an
280  IF(abs(h*rlat1-90).LT.tinyreal) THEN
281  xp=1
282  yp=1
283  ELSE
284  dr=de/tan((rlat1+90)/2/dpr)**an
285  dlon1=mod(rlon1-orient+180+3600,360.)-180
286  xp=1-sin(an*dlon1/dpr)*dr/dxs
287  yp=1+cos(an*dlon1/dpr)*dr/dys
288  ENDIF
289  antr=1/(2*an)
290  de2=de**2
291  xmin=0
292  xmax=im+1
293  ymin=0
294  ymax=jm+1
295  nret=0
296  IF(PRESENT(crot).AND.PRESENT(srot))THEN
297  lrot=.true.
298  ELSE
299  lrot=.false.
300  ENDIF
301  IF(PRESENT(xlon).AND.PRESENT(xlat).AND.PRESENT(ylon).AND.PRESENT(ylat))THEN
302  lmap=.true.
303  ELSE
304  lmap=.false.
305  ENDIF
306  IF(PRESENT(area))THEN
307  larea=.true.
308  ELSE
309  larea=.false.
310  ENDIF
311  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
312  ! TRANSLATE GRID COORDINATES TO EARTH COORDINATES
313  IF(iopt.EQ.0.OR.iopt.EQ.1) THEN
314  !$OMP PARALLEL DO PRIVATE(N,DI,DJ,DR2,DR,DLON) REDUCTION(+:NRET) SCHEDULE(STATIC)
315  DO n=1,npts
316  IF(xpts(n).GE.xmin.AND.xpts(n).LE.xmax.AND. &
317  ypts(n).GE.ymin.AND.ypts(n).LE.ymax) THEN
318  di=h*(xpts(n)-xp)*dxs
319  dj=h*(ypts(n)-yp)*dys
320  dr2=di**2+dj**2
321  dr=sqrt(dr2)
322  IF(dr2.LT.de2*1.e-6) THEN
323  rlon(n)=0.
324  rlat(n)=h*90.
325  ELSE
326  rlon(n)=mod(orient+1./an*dpr*atan2(di,-dj)+3600,360.)
327  rlat(n)=(2*dpr*atan((de2/dr2)**antr)-90)
328  ENDIF
329  nret=nret+1
330  dlon=mod(rlon(n)-orient+180+3600,360.)-180
331  IF(lrot) CALL lambert_conf_vect_rot(dlon,crot(n),srot(n))
332  IF(lmap) CALL lambert_conf_map_jacob(rlat(n),fill, dlon, dr, &
333  xlon(n),xlat(n),ylon(n),ylat(n))
334  IF(larea) CALL lambert_conf_grid_area(rlat(n),fill,dr,area(n))
335  ELSE
336  rlon(n)=fill
337  rlat(n)=fill
338  ENDIF
339  ENDDO
340  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
341  ! TRANSLATE EARTH COORDINATES TO GRID COORDINATES
342  ELSEIF(iopt.EQ.-1) THEN
343  !$OMP PARALLEL DO PRIVATE(N,DR,DLON) REDUCTION(+:NRET) SCHEDULE(STATIC)
344  DO n=1,npts
345  IF(abs(rlon(n)).LT.(360.+tinyreal).AND.abs(rlat(n)).LT.(90.+tinyreal).AND. &
346  abs(h*rlat(n)+90).GT.tinyreal) THEN
347  dr=h*de*tan((90-rlat(n))/2/dpr)**an
348  dlon=mod(rlon(n)-orient+180+3600,360.)-180
349  xpts(n)=xp+h*sin(an*dlon/dpr)*dr/dxs
350  ypts(n)=yp-h*cos(an*dlon/dpr)*dr/dys
351  IF(xpts(n).GE.xmin.AND.xpts(n).LE.xmax.AND. &
352  ypts(n).GE.ymin.AND.ypts(n).LE.ymax) THEN
353  nret=nret+1
354  IF(lrot) CALL lambert_conf_vect_rot(dlon,crot(n),srot(n))
355  IF(lmap) CALL lambert_conf_map_jacob(rlat(n),fill,dlon,dr, &
356  xlon(n),xlat(n),ylon(n),ylat(n))
357  IF(larea) CALL lambert_conf_grid_area(rlat(n),fill,dr,area(n))
358  ELSE
359  xpts(n)=fill
360  ypts(n)=fill
361  ENDIF
362  ELSE
363  xpts(n)=fill
364  ypts(n)=fill
365  ENDIF
366  ENDDO
367  !$OMP END PARALLEL DO
368  ENDIF
369  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
370  END SUBROUTINE gdswzd_lambert_conf
371 
390  SUBROUTINE lambert_conf_vect_rot(DLON,CROT,SROT)
391  IMPLICIT NONE
392  REAL, INTENT( IN) :: DLON
393  REAL, INTENT( OUT) :: CROT, SROT
394 
395  IF(irot.EQ.1) THEN
396  crot=cos(an*dlon/dpr)
397  srot=sin(an*dlon/dpr)
398  ELSE
399  crot=1.
400  srot=0.
401  ENDIF
402 
403  END SUBROUTINE lambert_conf_vect_rot
404 
427  SUBROUTINE lambert_conf_map_jacob(RLAT,FILL,DLON,DR,XLON,XLAT,YLON,YLAT)
428  IMPLICIT NONE
429 
430  REAL, INTENT(IN ) :: RLAT, FILL, DLON, DR
431  REAL, INTENT( OUT) :: XLON, XLAT, YLON, YLAT
432 
433  REAL :: CLAT
434 
435  clat=cos(rlat/dpr)
436  IF(clat.LE.0.OR.dr.LE.0) THEN
437  xlon=fill
438  xlat=fill
439  ylon=fill
440  ylat=fill
441  ELSE
442  xlon=h*cos(an*dlon/dpr)*an/dpr*dr/dxs
443  xlat=-h*sin(an*dlon/dpr)*an/dpr*dr/dxs/clat
444  ylon=h*sin(an*dlon/dpr)*an/dpr*dr/dys
445  ylat=h*cos(an*dlon/dpr)*an/dpr*dr/dys/clat
446  ENDIF
447 
448  END SUBROUTINE lambert_conf_map_jacob
449 
468  SUBROUTINE lambert_conf_grid_area(RLAT,FILL,DR,AREA)
469  IMPLICIT NONE
470 
471  REAL, INTENT(IN ) :: RLAT
472  REAL, INTENT(IN ) :: FILL
473  REAL, INTENT(IN ) :: DR
474  REAL, INTENT( OUT) :: AREA
475 
476  REAL :: CLAT
477 
478  clat=cos(rlat/dpr)
479  IF(clat.LE.0.OR.dr.LE.0) THEN
480  area=fill
481  ELSE
482  area=rerth**2*clat**2*abs(dxs)*abs(dys)/(an*dr)**2
483  ENDIF
484 
485  END SUBROUTINE lambert_conf_grid_area
486 
487 end module ip_lambert_conf_grid_mod
488 
void gdswzd(int igdtnum, int *igdtmpl, int igdtlen, int iopt, int npts, float fill, float *xpts, float *ypts, float *rlon, float *rlat, int *nret, float *crot, float *srot, float *xlon, float *xlat, float *ylon, float *ylat, float *area)
gdswzd() interface for C for _4 build of library.
Determine earth radius and shape.
Module containing common constants.
Users derived type grid descriptor objects to abstract away the raw GRIB1 and GRIB2 grid definitions.
Abstract ip_grid type.
Definition: ip_grid_mod.F90:10
Lambert conformal grib decoder and grid coordinate transformations.
subroutine lambert_conf_grid_area(RLAT, FILL, DR, AREA)
Grid box area for lambert conformal conical.
real dxs
x-direction grid length adjusted for scan mode.
subroutine init_grib1(self, g1_desc)
Initializes a Lambert Conformal grid given a grib1_descriptor object.
subroutine lambert_conf_vect_rot(DLON, CROT, SROT)
Vector rotation fields for lambert conformal conical.
subroutine lambert_conf_map_jacob(RLAT, FILL, DLON, DR, XLON, XLAT, YLON, YLAT)
Map jacobians for lambert conformal conical.
subroutine gdswzd_lambert_conf(self, IOPT, NPTS, FILL, XPTS, YPTS, RLON, RLAT, NRET, CROT, SROT, XLON, XLAT, YLON, YLAT, AREA)
GDS wizard for lambert conformal conical.
integer irot
vector rotation flag.
real rerth
Radius of the earth.
real dys
y-direction grid length adjusted for scan model.
subroutine init_grib2(self, g2_desc)
Initializes a Lambert Conformal grid given a grib2_descriptor object.
Descriptor representing a grib1 grib descriptor section (GDS) with an integer array.
Abstract grid that holds fields and methods common to all grids.
Definition: ip_grid_mod.F90:58