source: flexpart.git/src/gridcheck_gfs.f90 @ 92fab65

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 92fab65 was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 17.6 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine gridcheck_gfs
5
6  !**********************************************************************
7  !                                                                     *
8  !             FLEXPART MODEL SUBROUTINE GRIDCHECK                     *
9  !                                                                     *
10  !**********************************************************************
11  !                                                                     *
12  !             AUTHOR:      G. WOTAWA                                  *
13  !             DATE:        1997-08-06                                 *
14  !             LAST UPDATE: 1997-10-10                                 *
15  !                                                                     *
16  !             Update:      1999-02-08, global fields allowed, A. Stohl*
17  !             CHANGE: 17/11/2005, Caroline Forster, GFS data          *
18  !             CHANGE: 11/01/2008, Harald Sodemann, GRIB1/2 input with *
19  !                                 ECMWF grib_api                      *
20  !             CHANGE: 03/12/2008, Harald Sodemann, update to f90 with *
21  !                                 ECMWF grib_api                      *
22  !                                                                     *
23  !   Unified ECMWF and GFS builds                                      *
24  !   Marian Harustak, 12.5.2017                                        *
25  !     - Renamed routine from gridcheck to gridcheck_gfs               *
26  !                                                                     *
27  !**********************************************************************
28  !                                                                     *
29  ! DESCRIPTION:                                                        *
30  !                                                                     *
31  ! THIS SUBROUTINE DETERMINES THE GRID SPECIFICATIONS (LOWER LEFT      *
32  ! LONGITUDE, LOWER LEFT LATITUDE, NUMBER OF GRID POINTS, GRID DIST-   *
33  ! ANCE AND VERTICAL DISCRETIZATION OF THE ECMWF MODEL) FROM THE       *
34  ! GRIB HEADER OF THE FIRST INPUT FILE. THE CONSISTANCY (NO CHANGES    *
35  ! WITHIN ONE FLEXPART RUN) IS CHECKED IN THE ROUTINE "READWIND" AT    *
36  ! ANY CALL.                                                           *
37  !                                                                     *
38  ! XLON0                geographical longitude of lower left gridpoint *
39  ! YLAT0                geographical latitude of lower left gridpoint  *
40  ! NX                   number of grid points x-direction              *
41  ! NY                   number of grid points y-direction              *
42  ! DX                   grid distance x-direction                      *
43  ! DY                   grid distance y-direction                      *
44  ! NUVZ                 number of grid points for horizontal wind      *
45  !                      components in z direction                      *
46  ! NWZ                  number of grid points for vertical wind        *
47  !                      component in z direction                       *
48  ! sizesouth, sizenorth give the map scale (i.e. number of virtual grid*
49  !                      points of the polar stereographic grid):       *
50  !                      used to check the CFL criterion                *
51  ! UVHEIGHT(1)-         heights of gridpoints where u and v are        *
52  ! UVHEIGHT(NUVZ)       given                                          *
53  ! WHEIGHT(1)-          heights of gridpoints where w is given         *
54  ! WHEIGHT(NWZ)                                                        *
55  !                                                                     *
56  !**********************************************************************
57
58  use grib_api
59  use par_mod
60  use com_mod
61  use conv_mod
62  use cmapf_mod, only: stlmbr,stcm2p
63
64  implicit none
65
66  !HSO  parameters for grib_api
67  integer :: ifile
68  integer :: iret
69  integer :: igrib
70  real(kind=4) :: xaux1,xaux2,yaux1,yaux2
71  real(kind=8) :: xaux1in,xaux2in,yaux1in,yaux2in
72  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
73  !HSO  end
74  integer :: ix,jy,i,ifn,ifield,j,k,iumax,iwmax,numskip
75  real :: sizesouth,sizenorth,xauxa,pint
76  real :: akm_usort(nwzmax)
77  real,parameter :: eps=0.0001
78
79  ! NCEP GFS
80  real :: pres(nwzmax), help
81
82  integer :: i179,i180,i181
83
84  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
85
86  integer :: isec1(8),isec2(3)
87  real(kind=4) :: zsec4(jpunp)
88  character(len=1) :: opt
89
90  !HSO  grib api error messages
91  character(len=24) :: gribErrorMsg = 'Error reading grib file'
92  character(len=20) :: gribFunction = 'gridcheckwind_gfs'
93  !
94  if (numbnests.ge.1) then
95  write(*,*) ' ###########################################'
96  write(*,*) ' FLEXPART ERROR SUBROUTINE GRIDCHECK:'
97  write(*,*) ' NO NESTED WINDFIELDAS ALLOWED FOR GFS!      '
98  write(*,*) ' ###########################################'
99  stop
100  endif
101
102  iumax=0
103  iwmax=0
104
105  if(ideltas.gt.0) then
106    ifn=1
107  else
108    ifn=numbwf
109  endif
110  !
111  ! OPENING OF DATA FILE (GRIB CODE)
112  !
1135   call grib_open_file(ifile,path(3)(1:length(3)) &
114         //trim(wfname(ifn)),'r',iret)
115  if (iret.ne.GRIB_SUCCESS) then
116    goto 999   ! ERROR DETECTED
117  endif
118  !turn on support for multi fields messages
119  call grib_multi_support_on
120
121  ifield=0
12210   ifield=ifield+1
123  !
124  ! GET NEXT FIELDS
125  !
126  call grib_new_from_file(ifile,igrib,iret)
127  if (iret.eq.GRIB_END_OF_FILE )  then
128    goto 30    ! EOF DETECTED
129  elseif (iret.ne.GRIB_SUCCESS) then
130    goto 999   ! ERROR DETECTED
131  endif
132
133  !first see if we read GRIB1 or GRIB2
134  call grib_get_int(igrib,'editionNumber',gribVer,iret)
135  call grib_check(iret,gribFunction,gribErrorMsg)
136
137  if (gribVer.eq.1) then ! GRIB Edition 1
138
139  !read the grib1 identifiers
140  call grib_get_int(igrib,'indicatorOfParameter',isec1(6),iret)
141  call grib_check(iret,gribFunction,gribErrorMsg)
142  call grib_get_int(igrib,'indicatorOfTypeOfLevel',isec1(7),iret)
143  call grib_check(iret,gribFunction,gribErrorMsg)
144  call grib_get_int(igrib,'level',isec1(8),iret)
145  call grib_check(iret,gribFunction,gribErrorMsg)
146
147  !get the size and data of the values array
148  call grib_get_real4_array(igrib,'values',zsec4,iret)
149  call grib_check(iret,gribFunction,gribErrorMsg)
150
151  else ! GRIB Edition 2
152
153  !read the grib2 identifiers
154  call grib_get_int(igrib,'discipline',discipl,iret)
155  call grib_check(iret,gribFunction,gribErrorMsg)
156  call grib_get_int(igrib,'parameterCategory',parCat,iret)
157  call grib_check(iret,gribFunction,gribErrorMsg)
158  call grib_get_int(igrib,'parameterNumber',parNum,iret)
159  call grib_check(iret,gribFunction,gribErrorMsg)
160  call grib_get_int(igrib,'typeOfFirstFixedSurface',typSurf,iret)
161  call grib_check(iret,gribFunction,gribErrorMsg)
162  call grib_get_int(igrib,'scaledValueOfFirstFixedSurface', &
163       valSurf,iret)
164  call grib_check(iret,gribFunction,gribErrorMsg)
165
166  !convert to grib1 identifiers
167  isec1(6)=-1
168  isec1(7)=-1
169  isec1(8)=-1
170  if ((parCat.eq.2).and.(parNum.eq.2).and.(typSurf.eq.100)) then ! U
171    isec1(6)=33          ! indicatorOfParameter
172    isec1(7)=100         ! indicatorOfTypeOfLevel
173    isec1(8)=valSurf/100 ! level, convert to hPa
174  elseif ((parCat.eq.3).and.(parNum.eq.5).and.(typSurf.eq.1)) then ! TOPO
175    isec1(6)=7           ! indicatorOfParameter
176    isec1(7)=1           ! indicatorOfTypeOfLevel
177    isec1(8)=0
178  elseif ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.1) &
179       .and.(discipl.eq.2)) then ! LSM
180    isec1(6)=81          ! indicatorOfParameter
181    isec1(7)=1           ! indicatorOfTypeOfLevel
182    isec1(8)=0
183  endif
184
185  if (isec1(6).ne.-1) then
186  !  get the size and data of the values array
187    call grib_get_real4_array(igrib,'values',zsec4,iret)
188    call grib_check(iret,gribFunction,gribErrorMsg)
189  endif
190
191  endif ! gribVer
192
193  if(ifield.eq.1) then
194
195  !get the required fields from section 2
196  !store compatible to gribex input
197  call grib_get_int(igrib,'numberOfPointsAlongAParallel', &
198       isec2(2),iret)
199  call grib_check(iret,gribFunction,gribErrorMsg)
200  call grib_get_int(igrib,'numberOfPointsAlongAMeridian', &
201       isec2(3),iret)
202  call grib_check(iret,gribFunction,gribErrorMsg)
203  call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
204       xaux1in,iret)
205  call grib_check(iret,gribFunction,gribErrorMsg)
206  call grib_get_real8(igrib,'longitudeOfLastGridPointInDegrees', &
207       xaux2in,iret)
208  call grib_check(iret,gribFunction,gribErrorMsg)
209  call grib_get_real8(igrib,'latitudeOfLastGridPointInDegrees', &
210       yaux1in,iret)
211  call grib_check(iret,gribFunction,gribErrorMsg)
212  call grib_get_real8(igrib,'latitudeOfFirstGridPointInDegrees', &
213       yaux2in,iret)
214  call grib_check(iret,gribFunction,gribErrorMsg)
215
216  ! Fix for flexpart.eu ticket #48
217  if (xaux2in.lt.0) xaux2in = 359.0
218
219  xaux1=xaux1in
220  xaux2=xaux2in
221  yaux1=yaux1in
222  yaux2=yaux2in
223
224  nxfield=isec2(2)
225  ny=isec2(3)
226  if((abs(xaux1).lt.eps).and.(xaux2.ge.359)) then ! NCEP DATA FROM 0 TO
227    xaux1=-179.0                             ! 359 DEG EAST ->
228    xaux2=-179.0+360.-360./real(nxfield)    ! TRANSFORMED TO -179
229  endif                                      ! TO 180 DEG EAST
230  if (xaux1.gt.180) xaux1=xaux1-360.0
231  if (xaux2.gt.180) xaux2=xaux2-360.0
232  if (xaux1.lt.-180) xaux1=xaux1+360.0
233  if (xaux2.lt.-180) xaux2=xaux2+360.0
234  if (xaux2.lt.xaux1) xaux2=xaux2+360.
235  xlon0=xaux1
236  ylat0=yaux1
237  dx=(xaux2-xaux1)/real(nxfield-1)
238  dy=(yaux2-yaux1)/real(ny-1)
239  dxconst=180./(dx*r_earth*pi)
240  dyconst=180./(dy*r_earth*pi)
241  !HSO end edits
242
243
244  ! Check whether fields are global
245  ! If they contain the poles, specify polar stereographic map
246  ! projections using the stlmbr- and stcm2p-calls
247  !***********************************************************
248
249    xauxa=abs(xaux2+dx-360.-xaux1)
250    if (xauxa.lt.0.001) then
251      nx=nxfield+1                 ! field is cyclic
252      xglobal=.true.
253      if (abs(nxshift).ge.nx) &
254           stop 'nxshift in file par_mod is too large'
255      xlon0=xlon0+real(nxshift)*dx
256    else
257      nx=nxfield
258      xglobal=.false.
259      if (nxshift.ne.0) &
260           stop 'nxshift (par_mod) must be zero for non-global domain'
261    endif
262    nxmin1=nx-1
263    nymin1=ny-1
264    if (xlon0.gt.180.) xlon0=xlon0-360.
265    xauxa=abs(yaux1+90.)
266    if (xglobal.and.xauxa.lt.0.001) then
267      sglobal=.true.               ! field contains south pole
268  ! Enhance the map scale by factor 3 (*2=6) compared to north-south
269  ! map scale
270      sizesouth=6.*(switchsouth+90.)/dy
271      call stlmbr(southpolemap,-90.,0.)
272      call stcm2p(southpolemap,0.,0.,switchsouth,0.,sizesouth, &
273           sizesouth,switchsouth,180.)
274      switchsouthg=(switchsouth-ylat0)/dy
275    else
276      sglobal=.false.
277      switchsouthg=999999.
278    endif
279    xauxa=abs(yaux2-90.)
280    if (xglobal.and.xauxa.lt.0.001) then
281      nglobal=.true.               ! field contains north pole
282  ! Enhance the map scale by factor 3 (*2=6) compared to north-south
283  ! map scale
284      sizenorth=6.*(90.-switchnorth)/dy
285      call stlmbr(northpolemap,90.,0.)
286      call stcm2p(northpolemap,0.,0.,switchnorth,0.,sizenorth, &
287           sizenorth,switchnorth,180.)
288      switchnorthg=(switchnorth-ylat0)/dy
289    else
290      nglobal=.false.
291      switchnorthg=999999.
292    endif
293  endif ! ifield.eq.1
294
295  if (nxshift.lt.0) stop 'nxshift (par_mod) must not be negative'
296  if (nxshift.ge.nxfield) stop 'nxshift (par_mod) too large'
297
298  ! NCEP ISOBARIC LEVELS
299  !*********************
300
301  if((isec1(6).eq.33).and.(isec1(7).eq.100)) then ! check for U wind
302    iumax=iumax+1
303    pres(iumax)=real(isec1(8))*100.0
304  endif
305
306
307  i179=nint(179./dx)
308  if (dx.lt.0.7) then
309    i180=nint(180./dx)+1    ! 0.5 deg data
310  else
311    i180=nint(179./dx)+1    ! 1 deg data
312  endif
313  i181=i180+1
314
315
316  ! NCEP TERRAIN
317  !*************
318
319  if((isec1(6).eq.007).and.(isec1(7).eq.001)) then
320    do jy=0,ny-1
321      do ix=0,nxfield-1
322        help=zsec4(nxfield*(ny-jy-1)+ix+1)
323        if(ix.le.i180) then
324          oro(i179+ix,jy)=help
325          excessoro(i179+ix,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
326        else
327          oro(ix-i181,jy)=help
328          excessoro(ix-i181,jy)=0.0 ! ISOBARIC SURFACES: SUBGRID TERRAIN DISREGARDED
329        endif
330      end do
331    end do
332  endif
333
334  ! NCEP LAND SEA MASK
335  !*******************
336
337  if((isec1(6).eq.081).and.(isec1(7).eq.001)) then
338    do jy=0,ny-1
339      do ix=0,nxfield-1
340        help=zsec4(nxfield*(ny-jy-1)+ix+1)
341        if(ix.le.i180) then
342          lsm(i179+ix,jy)=help
343        else
344          lsm(ix-i181,jy)=help
345        endif
346      end do
347    end do
348  endif
349
350  call grib_release(igrib)
351
352  goto 10                      !! READ NEXT LEVEL OR PARAMETER
353  !
354  ! CLOSING OF INPUT DATA FILE
355  !
356
357  ! HSO
35830   continue
359  call grib_close_file(ifile)
360  ! HSO end edits
361
362  nuvz=iumax
363  nwz =iumax
364  nlev_ec=iumax
365
366  if (nx.gt.nxmax) then
367   write(*,*) 'FLEXPART error: Too many grid points in x direction.'
368    write(*,*) 'Reduce resolution of wind fields.'
369    write(*,*) 'Or change parameter settings in file par_mod.'
370    write(*,*) nx,nxmax
371    stop
372  endif
373
374  if (ny.gt.nymax) then
375   write(*,*) 'FLEXPART error: Too many grid points in y direction.'
376    write(*,*) 'Reduce resolution of wind fields.'
377    write(*,*) 'Or change parameter settings in file par_mod.'
378    write(*,*) ny,nymax
379    stop
380  endif
381
382  if (nuvz.gt.nuvzmax) then
383    write(*,*) 'FLEXPART error: Too many u,v grid points in z '// &
384         'direction.'
385    write(*,*) 'Reduce resolution of wind fields.'
386    write(*,*) 'Or change parameter settings in file par_mod.'
387    write(*,*) nuvz,nuvzmax
388    stop
389  endif
390
391  if (nwz.gt.nwzmax) then
392    write(*,*) 'FLEXPART error: Too many w grid points in z '// &
393         'direction.'
394    write(*,*) 'Reduce resolution of wind fields.'
395    write(*,*) 'Or change parameter settings in file par_mod.'
396    write(*,*) nwz,nwzmax
397    stop
398  endif
399
400  ! If desired, shift all grids by nxshift grid cells
401  !**************************************************
402
403  if (xglobal) then
404    call shift_field_0(oro,nxfield,ny)
405    call shift_field_0(lsm,nxfield,ny)
406    call shift_field_0(excessoro,nxfield,ny)
407  endif
408
409  ! Output of grid info
410  !********************
411
412  if (lroot) then
413    write(*,*)
414    write(*,*)
415    write(*,'(a,2i7)') 'Vertical levels in NCEP data: ', &
416         nuvz,nwz
417    write(*,*)
418    write(*,'(a)') 'Mother domain:'
419    write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Longitude range: ', &
420         xlon0,' to ',xlon0+(nx-1)*dx,'   Grid distance: ',dx
421    write(*,'(a,f10.2,a1,f10.2,a,f10.2)') '  Latitude range : ', &
422         ylat0,' to ',ylat0+(ny-1)*dy,'   Grid distance: ',dy
423    write(*,*)
424  end if
425
426  ! CALCULATE VERTICAL DISCRETIZATION OF ECMWF MODEL
427  ! PARAMETER akm,bkm DESCRIBE THE HYBRID "ETA" COORDINATE SYSTEM
428
429  numskip=nlev_ec-nuvz  ! number of ecmwf model layers not used
430                        ! by trajectory model
431  do i=1,nwz
432    j=numskip+i
433    k=nlev_ec+1+numskip+i
434    akm_usort(nwz-i+1)=pres(nwz-i+1)
435    bkm(nwz-i+1)=0.0
436  end do
437
438  !******************************
439  ! change Sabine Eckhardt: akm should always be in descending order ... readwind adapted!
440  !******************************
441      do i=1,nwz
442         if (akm_usort(1).gt.akm_usort(2)) then
443            akm(i)=akm_usort(i)
444         else
445            akm(i)=akm_usort(nwz-i+1)
446         endif
447      end do
448
449  !
450  ! CALCULATION OF AKZ, BKZ
451  ! AKZ,BKZ: model discretization parameters at the center of each model
452  !     layer
453  !
454  ! Assign the 10 m winds to an artificial model level with akz=0 and bkz=1.0,
455  ! i.e. ground level
456  !*****************************************************************************
457
458  do i=1,nuvz
459     akz(i)=akm(i)
460     bkz(i)=bkm(i)
461  end do
462
463  ! NOTE: In FLEXPART versions up to 4.0, the number of model levels was doubled
464  ! upon the transformation to z levels. In order to save computer memory, this is
465  ! not done anymore in the standard version. However, this option can still be
466  ! switched on by replacing the following lines with those below, that are
467  ! currently commented out. For this, similar changes are necessary in
468  ! verttransform.f and verttranform_nests.f
469  !*****************************************************************************
470
471  nz=nuvz
472  if (nz.gt.nzmax) stop 'nzmax too small'
473  do i=1,nuvz
474    aknew(i)=akz(i)
475    bknew(i)=bkz(i)
476  end do
477
478  ! Switch on following lines to use doubled vertical resolution
479  !*************************************************************
480  !nz=nuvz+nwz-1
481  !if (nz.gt.nzmax) stop 'nzmax too small'
482  !do 100 i=1,nwz
483  !  aknew(2*(i-1)+1)=akm(i)
484  !00     bknew(2*(i-1)+1)=bkm(i)
485  !do 110 i=2,nuvz
486  !  aknew(2*(i-1))=akz(i)
487  !10     bknew(2*(i-1))=bkz(i)
488  ! End doubled vertical resolution
489
490
491  ! Determine the uppermost level for which the convection scheme shall be applied
492  ! by assuming that there is no convection above 50 hPa (for standard SLP)
493  !*****************************************************************************
494
495  do i=1,nuvz-2
496    pint=akz(i)+bkz(i)*101325.
497    if (pint.lt.5000.) goto 96
498  end do
49996   nconvlev=i
500  if (nconvlev.gt.nconvlevmax-1) then
501    nconvlev=nconvlevmax-1
502    write(*,*) 'Attention, convection only calculated up to ', &
503         akz(nconvlev)+bkz(nconvlev)*1013.25,' hPa'
504  endif
505
506  return
507
508999   write(*,*)
509  write(*,*) ' ###########################################'// &
510       '###### '
511  write(*,*) '       TRAJECTORY MODEL SUBROUTINE GRIDCHECK:'
512  write(*,*) ' CAN NOT OPEN INPUT DATA FILE '//wfname(ifn)
513  write(*,*) ' ###########################################'// &
514       '###### '
515  write(*,*)
516  write(*,'(a)') '!!! PLEASE INSERT A NEW CD-ROM AND   !!!'
517  write(*,'(a)') '!!! PRESS ANY KEY TO CONTINUE...     !!!'
518  write(*,'(a)') '!!! ...OR TERMINATE FLEXPART PRESSING!!!'
519  write(*,'(a)') '!!! THE "X" KEY...                   !!!'
520  write(*,*)
521  read(*,'(a)') opt
522  if(opt.eq.'X') then
523    stop
524  else
525    goto 5
526  endif
527
528end subroutine gridcheck_gfs
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG