NCEPLIBS-ip 5.2.0
Loading...
Searching...
No Matches
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
37 procedure :: init_grib1
40 procedure :: init_grib2
46
47 INTEGER :: irot
48 REAL :: an
49 REAL :: dxs
50 REAL :: dys
51 REAL :: h
52 REAL :: rerth
53 REAL :: tinyreal=tiny(1.0)
54
55contains
56
63 subroutine init_grib1(self, g1_desc)
64 class(ip_lambert_conf_grid), intent(inout) :: self
65 type(grib1_descriptor), intent(in) :: g1_desc
66
67 real :: dx, dy, hi, hj
68 integer :: iproj, iscan, jscan
69
70 associate(kgds => g1_desc%gds)
71 self%rerth = 6.3712e6
72 self%eccen_squared = 0.0
73
74 self%IM=kgds(2)
75 self%JM=kgds(3)
76
77 self%RLAT1=kgds(4)*1.e-3
78 self%RLON1=kgds(5)*1.e-3
79
80 self%IROT=mod(kgds(6)/8,2)
81 self%ORIENT=kgds(7)*1.e-3
82
83 dx=kgds(8)
84 dy=kgds(9)
85
86 iproj=mod(kgds(10)/128,2)
87 iscan=mod(kgds(11)/128,2)
88 jscan=mod(kgds(11)/64,2)
89
90 self%RLATI1=kgds(12)*1.e-3
91 self%RLATI2=kgds(13)*1.e-3
92 self%H=(-1.)**iproj
93
94 hi=(-1.)**iscan
95 hj=(-1.)**(1-jscan)
96 self%DXS=dx*hi
97 self%DYS=dy*hj
98
99 self%iwrap = 0
100 self%jwrap1 = 0
101 self%jwrap2 = 0
102 self%nscan = mod(kgds(11) / 32, 2)
103 self%nscan_field_pos = self%nscan
104 self%kscan = 0
105 end associate
106
107 end subroutine init_grib1
108
115 subroutine init_grib2(self, g2_desc)
116 class(ip_lambert_conf_grid), intent(inout) :: self
117 type(grib2_descriptor), intent(in) :: g2_desc
118
119 real :: dx, dy, hi, hj
120 integer :: iproj, iscan, jscan
121
122
123 associate(igdtmpl => g2_desc%gdt_tmpl, igdtlen => g2_desc%gdt_len)
124 call earth_radius(igdtmpl, igdtlen, self%rerth, self%eccen_squared)
125
126 self%IM=igdtmpl(8)
127 self%JM=igdtmpl(9)
128
129 self%RLAT1=float(igdtmpl(10))*1.0e-6
130 self%RLON1=float(igdtmpl(11))*1.0e-6
131
132 self%IROT=mod(igdtmpl(12)/8,2)
133 self%ORIENT=float(igdtmpl(14))*1.0e-6
134
135 dx=float(igdtmpl(15))*1.0e-3
136 dy=float(igdtmpl(16))*1.0e-3
137
138 iproj=mod(igdtmpl(17)/128,2)
139 iscan=mod(igdtmpl(18)/128,2)
140 jscan=mod(igdtmpl(18)/64,2)
141
142 self%RLATI1=float(igdtmpl(19))*1.0e-6
143 self%RLATI2=float(igdtmpl(20))*1.0e-6
144
145 self%H=(-1.)**iproj
146 hi=(-1.)**iscan
147 hj=(-1.)**(1-jscan)
148 self%DXS=dx*hi
149 self%DYS=dy*hj
150
151 self%nscan = mod(igdtmpl(18) / 32, 2)
152 self%nscan_field_pos = self%nscan
153 self%iwrap = 0
154 self%jwrap1 = 0
155 self%jwrap2 = 0
156 self%kscan = 0
157 end associate
158 end subroutine init_grib2
159
222 SUBROUTINE gdswzd_lambert_conf(self,IOPT,NPTS,FILL, &
223 XPTS,YPTS,RLON,RLAT,NRET, &
224 CROT,SROT,XLON,XLAT,YLON,YLAT,AREA)
225 IMPLICIT NONE
226 !
227 class(ip_lambert_conf_grid), intent(in) :: self
228 INTEGER, INTENT(IN ) :: IOPT, NPTS
229 INTEGER, INTENT( OUT) :: NRET
230 !
231 REAL, INTENT(IN ) :: FILL
232 REAL, INTENT(INOUT) :: RLON(NPTS),RLAT(NPTS)
233 REAL, INTENT(INOUT) :: XPTS(NPTS),YPTS(NPTS)
234 REAL, OPTIONAL, INTENT( OUT) :: CROT(NPTS),SROT(NPTS)
235 REAL, OPTIONAL, INTENT( OUT) :: XLON(NPTS),XLAT(NPTS)
236 REAL, OPTIONAL, INTENT( OUT) :: YLON(NPTS),YLAT(NPTS),AREA(NPTS)
237 !
238 INTEGER :: IM, JM, N
239 !
240 LOGICAL :: LROT, LMAP, LAREA
241 !
242 REAL :: ANTR, DI, DJ
243 REAL :: DLON1
244 REAL :: DE, DE2, DR2
245 REAL :: ORIENT, RLAT1, RLON1
246 REAL :: RLATI1, RLATI2
247 REAL :: XMAX, XMIN, YMAX, YMIN, XP, YP
248 REAL :: DLON, DR
249 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
250 IF(PRESENT(crot)) crot=fill
251 IF(PRESENT(srot)) srot=fill
252 IF(PRESENT(xlon)) xlon=fill
253 IF(PRESENT(xlat)) xlat=fill
254 IF(PRESENT(ylon)) ylon=fill
255 IF(PRESENT(ylat)) ylat=fill
256 IF(PRESENT(area)) area=fill
257
258 im=self%im
259 jm=self%jm
260
261 rlat1=self%rlat1
262 rlon1=self%rlon1
263
264 irot=self%irot
265 orient=self%orient
266
267 rlati1=self%rlati1
268 rlati2=self%rlati2
269
270 h=self%h
271 dxs=self%dxs
272 dys=self%dys
273
274 rerth = self%rerth
275
276 IF(abs(rlati1-rlati2).LT.tinyreal) THEN
277 an=sin(rlati1/dpr)
278 ELSE
279 an=log(cos(rlati1/dpr)/cos(rlati2/dpr))/ &
280 log(tan((90-rlati1)/2/dpr)/tan((90-rlati2)/2/dpr))
281 ENDIF
282 de=rerth*cos(rlati1/dpr)*tan((rlati1+90)/2/dpr)**an/an
283 IF(abs(h*rlat1-90).LT.tinyreal) THEN
284 xp=1
285 yp=1
286 ELSE
287 dr=de/tan((rlat1+90)/2/dpr)**an
288 dlon1=mod(rlon1-orient+180+3600,360.)-180
289 xp=1-sin(an*dlon1/dpr)*dr/dxs
290 yp=1+cos(an*dlon1/dpr)*dr/dys
291 ENDIF
292 antr=1/(2*an)
293 de2=de**2
294 xmin=0
295 xmax=im+1
296 ymin=0
297 ymax=jm+1
298 nret=0
299 IF(PRESENT(crot).AND.PRESENT(srot))THEN
300 lrot=.true.
301 ELSE
302 lrot=.false.
303 ENDIF
304 IF(PRESENT(xlon).AND.PRESENT(xlat).AND.PRESENT(ylon).AND.PRESENT(ylat))THEN
305 lmap=.true.
306 ELSE
307 lmap=.false.
308 ENDIF
309 IF(PRESENT(area))THEN
310 larea=.true.
311 ELSE
312 larea=.false.
313 ENDIF
314 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
315 ! TRANSLATE GRID COORDINATES TO EARTH COORDINATES
316 IF(iopt.EQ.0.OR.iopt.EQ.1) THEN
317 !$OMP PARALLEL DO PRIVATE(N,DI,DJ,DR2,DR,DLON) REDUCTION(+:NRET) SCHEDULE(STATIC)
318 DO n=1,npts
319 IF(xpts(n).GE.xmin.AND.xpts(n).LE.xmax.AND. &
320 ypts(n).GE.ymin.AND.ypts(n).LE.ymax) THEN
321 di=h*(xpts(n)-xp)*dxs
322 dj=h*(ypts(n)-yp)*dys
323 dr2=di**2+dj**2
324 dr=sqrt(dr2)
325 IF(dr2.LT.de2*1.e-6) THEN
326 rlon(n)=0.
327 rlat(n)=h*90.
328 ELSE
329 rlon(n)=mod(orient+1./an*dpr*atan2(di,-dj)+3600,360.)
330 rlat(n)=(2*dpr*atan((de2/dr2)**antr)-90)
331 ENDIF
332 nret=nret+1
333 dlon=mod(rlon(n)-orient+180+3600,360.)-180
334 IF(lrot) CALL lambert_conf_vect_rot(dlon,crot(n),srot(n))
335 IF(lmap) CALL lambert_conf_map_jacob(rlat(n),fill, dlon, dr, &
336 xlon(n),xlat(n),ylon(n),ylat(n))
337 IF(larea) CALL lambert_conf_grid_area(rlat(n),fill,dr,area(n))
338 ELSE
339 rlon(n)=fill
340 rlat(n)=fill
341 ENDIF
342 ENDDO
343 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
344 ! TRANSLATE EARTH COORDINATES TO GRID COORDINATES
345 ELSEIF(iopt.EQ.-1) THEN
346 !$OMP PARALLEL DO PRIVATE(N,DR,DLON) REDUCTION(+:NRET) SCHEDULE(STATIC)
347 DO n=1,npts
348 IF(abs(rlon(n)).LT.(360.+tinyreal).AND.abs(rlat(n)).LT.(90.+tinyreal).AND. &
349 abs(h*rlat(n)+90).GT.tinyreal) THEN
350 dr=h*de*tan((90-rlat(n))/2/dpr)**an
351 dlon=mod(rlon(n)-orient+180+3600,360.)-180
352 xpts(n)=xp+h*sin(an*dlon/dpr)*dr/dxs
353 ypts(n)=yp-h*cos(an*dlon/dpr)*dr/dys
354 IF(xpts(n).GE.xmin.AND.xpts(n).LE.xmax.AND. &
355 ypts(n).GE.ymin.AND.ypts(n).LE.ymax) THEN
356 nret=nret+1
357 IF(lrot) CALL lambert_conf_vect_rot(dlon,crot(n),srot(n))
358 IF(lmap) CALL lambert_conf_map_jacob(rlat(n),fill,dlon,dr, &
359 xlon(n),xlat(n),ylon(n),ylat(n))
360 IF(larea) CALL lambert_conf_grid_area(rlat(n),fill,dr,area(n))
361 ELSE
362 xpts(n)=fill
363 ypts(n)=fill
364 ENDIF
365 ELSE
366 xpts(n)=fill
367 ypts(n)=fill
368 ENDIF
369 ENDDO
370 !$OMP END PARALLEL DO
371 ENDIF
372 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
373 END SUBROUTINE gdswzd_lambert_conf
374
393 SUBROUTINE lambert_conf_vect_rot(DLON,CROT,SROT)
394 IMPLICIT NONE
395 REAL, INTENT( IN) :: DLON
396 REAL, INTENT( OUT) :: CROT, SROT
397
398 IF(irot.EQ.1) THEN
399 crot=cos(an*dlon/dpr)
400 srot=sin(an*dlon/dpr)
401 ELSE
402 crot=1.
403 srot=0.
404 ENDIF
405
406 END SUBROUTINE lambert_conf_vect_rot
407
430 SUBROUTINE lambert_conf_map_jacob(RLAT,FILL,DLON,DR,XLON,XLAT,YLON,YLAT)
431 IMPLICIT NONE
432
433 REAL, INTENT(IN ) :: RLAT, FILL, DLON, DR
434 REAL, INTENT( OUT) :: XLON, XLAT, YLON, YLAT
435
436 REAL :: CLAT
437
438 clat=cos(rlat/dpr)
439 IF(clat.LE.0.OR.dr.LE.0) THEN
440 xlon=fill
441 xlat=fill
442 ylon=fill
443 ylat=fill
444 ELSE
445 xlon=h*cos(an*dlon/dpr)*an/dpr*dr/dxs
446 xlat=-h*sin(an*dlon/dpr)*an/dpr*dr/dxs/clat
447 ylon=h*sin(an*dlon/dpr)*an/dpr*dr/dys
448 ylat=h*cos(an*dlon/dpr)*an/dpr*dr/dys/clat
449 ENDIF
450
451 END SUBROUTINE lambert_conf_map_jacob
452
471 SUBROUTINE lambert_conf_grid_area(RLAT,FILL,DR,AREA)
472 IMPLICIT NONE
473
474 REAL, INTENT(IN ) :: RLAT
475 REAL, INTENT(IN ) :: FILL
476 REAL, INTENT(IN ) :: DR
477 REAL, INTENT( OUT) :: AREA
478
479 REAL :: CLAT
480
481 clat=cos(rlat/dpr)
482 IF(clat.LE.0.OR.dr.LE.0) THEN
483 area=fill
484 ELSE
485 area=rerth**2*clat**2*abs(dxs)*abs(dys)/(an*dr)**2
486 ENDIF
487
488 END SUBROUTINE lambert_conf_grid_area
489
491
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.
Lambert conformal grib decoder and grid coordinate transformations.
real dxs
x-direction grid length adjusted for scan mode.
subroutine lambert_conf_map_jacob(rlat, fill, dlon, dr, xlon, xlat, ylon, ylat)
Map jacobians for lambert conformal conical.
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.
integer irot
vector rotation flag.
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.
real dys
y-direction grid length adjusted for scan model.
subroutine lambert_conf_grid_area(rlat, fill, dr, area)
Grid box area for lambert conformal conical.
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.