source: flexpart.git/src/readwind_nests.f90 @ 3481cc1

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

move license from headers to a different file

  • Property mode set to 100644
File size: 18.3 KB
Line 
1subroutine readwind_nests(indj,n,uuhn,vvhn,wwhn)
2  !                           i   i  o    o    o
3  !*****************************************************************************
4  !                                                                            *
5  !     This routine reads the wind fields for the nested model domains.       *
6  !     It is similar to subroutine readwind, which reads the mother domain.   *
7  !                                                                            *
8  !     Authors: A. Stohl, G. Wotawa                                           *
9  !                                                                            *
10  !     8 February 1999                                                        *
11  !                                                                            *
12  !     Last update: 17 October 2000, A. Stohl                                 *
13  !                                                                            *
14  !*****************************************************************************
15  !  Changes, Bernd C. Krueger, Feb. 2001:                                     *
16  !        Variables tthn and qvhn (on eta coordinates) in common block        *
17  !  CHANGE: 11/01/2008, Harald Sodemann, GRIB1/2 input with ECMWF grib_api    *
18  !  CHANGE: 03/12/2008, Harald Sodemann, update to f90 with ECMWF grib_api    *
19  !*****************************************************************************
20
21  use grib_api
22  use par_mod
23  use com_mod
24
25  implicit none
26
27  !HSO  parameters for grib_api
28  integer :: ifile
29  integer :: iret
30  integer :: igrib
31  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
32  integer :: parId !!added by mc for making it consistent with new readwind.f90
33  integer :: gotGrid
34  !HSO  end
35
36  real :: uuhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
37  real :: vvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
38  real :: wwhn(0:nxmaxn-1,0:nymaxn-1,nwzmax,maxnests)
39  integer :: indj,i,j,k,n,levdiff2,ifield,iumax,iwmax,l
40
41  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
42
43  ! dimension of isec2 at least (22+n), where n is the number of parallels or
44  ! meridians in a quasi-regular (reduced) Gaussian or lat/long grid
45
46  ! dimension of zsec2 at least (10+nn), where nn is the number of vertical
47  ! coordinate parameters
48
49  integer :: isec1(56),isec2(22+nxmaxn+nymaxn)
50  real(kind=4) :: zsec4(jpunp)
51  real(kind=4) :: xaux,yaux
52  real(kind=8) :: xauxin,yauxin
53  real,parameter :: eps=1.e-4
54  real :: ewss(0:nxmaxn-1,0:nymaxn-1),nsss(0:nxmaxn-1,0:nymaxn-1)
55  real :: plev1,pmean,tv,fu,hlev1,ff10m,fflev1
56  real :: conversion_factor !added by mc to make it consistent with new gridchek.f90
57
58  logical :: hflswitch,strswitch
59
60  !HSO  grib api error messages
61  character(len=24) :: gribErrorMsg = 'Error reading grib file'
62  character(len=20) :: gribFunction = 'readwind_nests'
63
64  do l=1,numbnests
65    hflswitch=.false.
66    strswitch=.false.
67    levdiff2=nlev_ec-nwz+1
68    iumax=0
69    iwmax=0
70
71    ifile=0
72    igrib=0
73    iret=0
74
75  !
76  ! OPENING OF DATA FILE (GRIB CODE)
77  !
78
795   call grib_open_file(ifile,path(numpath+2*(l-1)+1) &
80         (1:length(numpath+2*(l-1)+1))//trim(wfnamen(l,indj)),'r')
81  if (iret.ne.GRIB_SUCCESS) then
82    goto 888   ! ERROR DETECTED
83  endif
84  !turn on support for multi fields messages */
85  !call grib_multi_support_on
86
87    gotGrid=0
88    ifield=0
8910   ifield=ifield+1
90  !
91  ! GET NEXT FIELDS
92  !
93  call grib_new_from_file(ifile,igrib,iret)
94  if (iret.eq.GRIB_END_OF_FILE)  then
95    goto 50    ! EOF DETECTED
96  elseif (iret.ne.GRIB_SUCCESS) then
97    goto 888   ! ERROR DETECTED
98  endif
99
100  !first see if we read GRIB1 or GRIB2
101  call grib_get_int(igrib,'editionNumber',gribVer,iret)
102  call grib_check(iret,gribFunction,gribErrorMsg)
103
104  if (gribVer.eq.1) then ! GRIB Edition 1
105
106  !print*,'GRiB Edition 1'
107  !read the grib2 identifiers
108  call grib_get_int(igrib,'indicatorOfParameter',isec1(6),iret)
109  call grib_check(iret,gribFunction,gribErrorMsg)
110  call grib_get_int(igrib,'level',isec1(8),iret)
111  call grib_check(iret,gribFunction,gribErrorMsg)
112
113  !change code for etadot to code for omega
114  if (isec1(6).eq.77) then
115    isec1(6)=135
116  endif
117
118  conversion_factor=1.
119
120
121  else
122
123  !print*,'GRiB Edition 2'
124  !read the grib2 identifiers
125  call grib_get_int(igrib,'discipline',discipl,iret)
126  call grib_check(iret,gribFunction,gribErrorMsg)
127  call grib_get_int(igrib,'parameterCategory',parCat,iret)
128  call grib_check(iret,gribFunction,gribErrorMsg)
129  call grib_get_int(igrib,'parameterNumber',parNum,iret)
130  call grib_check(iret,gribFunction,gribErrorMsg)
131  call grib_get_int(igrib,'typeOfFirstFixedSurface',typSurf,iret)
132  call grib_check(iret,gribFunction,gribErrorMsg)
133  call grib_get_int(igrib,'level',valSurf,iret)
134  call grib_check(iret,gribFunction,gribErrorMsg)
135  call grib_get_int(igrib,'paramId',parId,iret) !added by mc to make it consisitent with new readwind.f90
136  call grib_check(iret,gribFunction,gribErrorMsg) !added by mc to make it consisitent with new readwind.f90
137
138  !print*,discipl,parCat,parNum,typSurf,valSurf
139
140  !convert to grib1 identifiers
141  isec1(6)=-1
142  isec1(7)=-1
143  isec1(8)=-1
144  isec1(8)=valSurf     ! level
145   conversion_factor=1.
146  if ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! T
147    isec1(6)=130         ! indicatorOfParameter
148  elseif ((parCat.eq.2).and.(parNum.eq.2).and.(typSurf.eq.105)) then ! U
149    isec1(6)=131         ! indicatorOfParameter
150  elseif ((parCat.eq.2).and.(parNum.eq.3).and.(typSurf.eq.105)) then ! V
151    isec1(6)=132         ! indicatorOfParameter
152  elseif ((parCat.eq.1).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! Q
153    isec1(6)=133         ! indicatorOfParameter
154! ESO Cloud water is in a) fields CLWC and CIWC, *or* b) field QC
155    elseif ((parCat.eq.1).and.(parNum.eq.83).and.(typSurf.eq.105)) then ! clwc
156      isec1(6)=246         ! indicatorOfParameter
157    elseif ((parCat.eq.1).and.(parNum.eq.84).and.(typSurf.eq.105)) then ! ciwc
158      isec1(6)=247         ! indicatorOfParameter
159! ESO qc(=clwc+ciwc):
160    elseif ((parCat.eq.201).and.(parNum.eq.31).and.(typSurf.eq.105)) then ! qc
161      isec1(6)=201031         ! indicatorOfParameter
162  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.1)) then !SP
163    isec1(6)=134         ! indicatorOfParameter
164  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot !
165    isec1(6)=135         ! indicatorOfParameter
166  elseif ((parCat.eq.128).and.(parNum.eq.77)) then ! W, actually eta dot !added by mc to make it consisitent with new readwind.f90
167    isec1(6)=135         ! indicatorOfParameter    !added by mc to make it consisitent with new readwind.f90
168  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
169    isec1(6)=151         ! indicatorOfParameter
170  elseif ((parCat.eq.2).and.(parNum.eq.2).and.(typSurf.eq.103)) then ! 10U
171    isec1(6)=165         ! indicatorOfParameter
172  elseif ((parCat.eq.2).and.(parNum.eq.3).and.(typSurf.eq.103)) then ! 10V
173    isec1(6)=166         ! indicatorOfParameter
174  elseif ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.103)) then ! 2T
175    isec1(6)=167         ! indicatorOfParameter
176  elseif ((parCat.eq.0).and.(parNum.eq.6).and.(typSurf.eq.103)) then ! 2D
177    isec1(6)=168         ! indicatorOfParameter
178  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
179    isec1(6)=141         ! indicatorOfParameter
180    conversion_factor=1000. !added by mc to make it consisitent with new readwind.f90
181  elseif ((parCat.eq.6).and.(parNum.eq.1) .or. parId .eq. 164) then ! CC !added by mc to make it consisitent with new readwind.f90
182    isec1(6)=164         ! indicatorOfParameter
183  elseif ((parCat.eq.1).and.(parNum.eq.9) .or. parId .eq. 142) then ! LSP !added by mc to make it consisitent with new readwind.f90
184    isec1(6)=142         ! indicatorOfParameter
185  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
186    isec1(6)=143         ! indicatorOfParameter
187    conversion_factor=1000. !added by mc to make it consisitent with new readwind.f90
188  elseif ((parCat.eq.0).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SHF
189    isec1(6)=146         ! indicatorOfParameter
190  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
191    isec1(6)=176         ! indicatorOfParameter
192  elseif ((parCat.eq.2).and.(parNum.eq.38) .or. parId .eq. 180) then ! EWSS !added by mc to make it consisitent with new readwind.f90
193    isec1(6)=180         ! indicatorOfParameter
194  elseif ((parCat.eq.2).and.(parNum.eq.37) .or. parId .eq. 181) then ! NSSS !added by mc to make it consisitent with new readwind.f90
195    isec1(6)=181         ! indicatorOfParameter
196  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
197    isec1(6)=129         ! indicatorOfParameter
198   elseif ((parCat.eq.3).and.(parNum.eq.7) .or. parId .eq. 160) then ! SDO !added by mc to make it consisitent with new readwind.f90
199    isec1(6)=160         ! indicatorOfParameter
200  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
201       (typSurf.eq.1)) then ! LSM
202    isec1(6)=172         ! indicatorOfParameter
203  elseif (parNum.eq.152) then
204      isec1(6)=152         ! avoid warning for lnsp       
205  else
206    print*,'***WARNING: undefined GRiB2 message found!',discipl, &
207         parCat,parNum,typSurf
208  endif
209  if(parId .ne. isec1(6) .and. parId .ne. 77) then !added by mc to make it consisitent with new readwind.f90
210    write(*,*) 'parId',parId, 'isec1(6)',isec1(6)  !
211!    stop
212  endif
213
214  endif
215
216  !HSO  get the size and data of the values array
217  if (isec1(6).ne.-1) then
218    call grib_get_real4_array(igrib,'values',zsec4,iret)
219    call grib_check(iret,gribFunction,gribErrorMsg)
220  endif
221
222  !HSO  get the required fields from section 2 in a gribex compatible manner
223  if(ifield.eq.1) then
224  call grib_get_int(igrib,'numberOfPointsAlongAParallel', &
225       isec2(2),iret)
226  call grib_check(iret,gribFunction,gribErrorMsg)
227  call grib_get_int(igrib,'numberOfPointsAlongAMeridian', &
228       isec2(3),iret)
229  call grib_check(iret,gribFunction,gribErrorMsg)
230  call grib_get_int(igrib,'numberOfVerticalCoordinateValues', &
231       isec2(12))
232  call grib_check(iret,gribFunction,gribErrorMsg)
233  ! CHECK GRID SPECIFICATIONS
234  if(isec2(2).ne.nxn(l)) stop &
235  'READWIND: NX NOT CONSISTENT FOR A NESTING LEVEL'
236  if(isec2(3).ne.nyn(l)) stop &
237  'READWIND: NY NOT CONSISTENT FOR A NESTING LEVEL'
238  if(isec2(12)/2-1.ne.nlev_ec) stop 'READWIND: VERTICAL DISCRET&
239       &IZATION NOT CONSISTENT FOR A NESTING LEVEL'
240  endif ! ifield
241
242  !HSO  get the second part of the grid dimensions only from GRiB1 messages
243 if (isec1(6) .eq. 167 .and. (gotGrid.eq.0)) then ! !added by mc to make it consisitent with new readwind.f90
244    call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
245         xauxin,iret)
246    call grib_check(iret,gribFunction,gribErrorMsg)
247    call grib_get_real8(igrib,'latitudeOfLastGridPointInDegrees', &
248         yauxin,iret)
249    call grib_check(iret,gribFunction,gribErrorMsg)
250    if (xauxin.gt.180.) xauxin=xauxin-360.0
251    if (xauxin.lt.-180.) xauxin=xauxin+360.0
252
253    xaux=xauxin
254    yaux=yauxin
255    if (abs(xaux-xlon0n(l)).gt.eps) &
256    stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT FOR A NESTING LEVEL'
257    if (abs(yaux-ylat0n(l)).gt.eps) &
258    stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT FOR A NESTING LEVEL'
259    gotGrid=1
260  endif
261
262    do j=0,nyn(l)-1
263      do i=0,nxn(l)-1
264        k=isec1(8)
265        if(isec1(6).eq.130) tthn(i,j,nlev_ec-k+2,n,l)= &!! TEMPERATURE
266             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
267        if(isec1(6).eq.131) uuhn(i,j,nlev_ec-k+2,l)= &!! U VELOCITY
268             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
269        if(isec1(6).eq.132) vvhn(i,j,nlev_ec-k+2,l)= &!! V VELOCITY
270             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
271        if(isec1(6).eq.133) then                         !! SPEC. HUMIDITY
272          qvhn(i,j,nlev_ec-k+2,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
273          if (qvhn(i,j,nlev_ec-k+2,n,l) .lt. 0.) &
274               qvhn(i,j,nlev_ec-k+2,n,l) = 0.
275  !          this is necessary because the gridded data may contain
276  !          spurious negative values
277        endif
278        if(isec1(6).eq.134) psn(i,j,1,n,l)= &!! SURF. PRESS.
279             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
280        if(isec1(6).eq.135) wwhn(i,j,nlev_ec-k+1,l)= &!! W VELOCITY
281             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
282        if(isec1(6).eq.141) sdn(i,j,1,n,l)= &!! SNOW DEPTH
283             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)/conversion_factor !added by mc to make it consisitent with new readwind.f90!
284        if(isec1(6).eq.151) msln(i,j,1,n,l)= &!! SEA LEVEL PRESS.
285             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
286        if(isec1(6).eq.164) tccn(i,j,1,n,l)= &!! CLOUD COVER
287             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
288        if(isec1(6).eq.165) u10n(i,j,1,n,l)= &!! 10 M U VELOCITY
289             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
290        if(isec1(6).eq.166) v10n(i,j,1,n,l)= &!! 10 M V VELOCITY
291             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
292        if(isec1(6).eq.167) tt2n(i,j,1,n,l)= &!! 2 M TEMPERATURE
293             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
294        if(isec1(6).eq.168) td2n(i,j,1,n,l)= &!! 2 M DEW POINT
295             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
296        if(isec1(6).eq.142) then                         !! LARGE SCALE PREC.
297          lsprecn(i,j,1,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
298          if (lsprecn(i,j,1,n,l).lt.0.) lsprecn(i,j,1,n,l)=0.
299        endif
300        if(isec1(6).eq.143) then                         !! CONVECTIVE PREC.
301          convprecn(i,j,1,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)/conversion_factor !added by mc to make it consisitent with new readwind.f90
302          if (convprecn(i,j,1,n,l).lt.0.) convprecn(i,j,1,n,l)=0.
303        endif
304        if(isec1(6).eq.146) sshfn(i,j,1,n,l)= &!! SENS. HEAT FLUX
305             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
306        if((isec1(6).eq.146).and. &
307             (zsec4(nxn(l)*(nyn(l)-j-1)+i+1).ne.0.)) hflswitch=.true.    ! Heat flux available
308        if(isec1(6).eq.176) then                         !! SOLAR RADIATION
309          ssrn(i,j,1,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
310          if (ssrn(i,j,1,n,l).lt.0.) ssrn(i,j,1,n,l)=0.
311        endif
312        if(isec1(6).eq.180) ewss(i,j)= &!! EW SURFACE STRESS
313             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
314        if(isec1(6).eq.181) nsss(i,j)= &!! NS SURFACE STRESS
315             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
316        if(((isec1(6).eq.180).or.(isec1(6).eq.181)).and. &
317             (zsec4(nxn(l)*(nyn(l)-j-1)+i+1).ne.0.)) strswitch=.true.    ! stress available
318        if(isec1(6).eq.129) oron(i,j,l)= &!! ECMWF OROGRAPHY
319             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)/ga
320        if(isec1(6).eq.160) excessoron(i,j,l)= &!! STANDARD DEVIATION OF OROGRAPHY
321             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
322        if(isec1(6).eq.172) lsmn(i,j,l)= &!! ECMWF LAND SEA MASK
323             zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
324        if(isec1(6).eq.131) iumax=max(iumax,nlev_ec-k+1)
325        if(isec1(6).eq.135) iwmax=max(iwmax,nlev_ec-k+1)
326
327! ESO TODO:
328! -add check for if one of clwc/ciwc missing (error),
329!    also if all 3 cw fields present, use qc and disregard the others
330        if(isec1(6).eq.246) then  !! CLWC  Cloud liquid water content [kg/kg]
331          clwchn(i,j,nlev_ec-k+2,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
332          readclouds_nest(l)=.true.
333          sumclouds_nest(l)=.false.
334        endif
335        if(isec1(6).eq.247) then  !! CIWC  Cloud ice water content
336          ciwchn(i,j,nlev_ec-k+2,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
337        endif
338!ZHG end
339!ESO read qc (=clwc+ciwc)
340        if(isec1(6).eq.201031) then  !! QC  Cloud liquid water content [kg/kg]
341          clwchn(i,j,nlev_ec-k+2,n,l)=zsec4(nxn(l)*(nyn(l)-j-1)+i+1)
342          readclouds_nest(l)=.true.
343          sumclouds_nest(l)=.true.
344        endif
345
346
347      end do
348    end do
349
350  call grib_release(igrib)
351  goto 10                      !! READ NEXT LEVEL OR PARAMETER
352  !
353  ! CLOSING OF INPUT DATA FILE
354  !
35550   call grib_close_file(ifile)
356
357  !error message if no fields found with correct first longitude in it
358  if (gotGrid.eq.0) then
359    print*,'***ERROR: input file needs to contain GRiB1 formatted'// &
360         'messages'
361    stop
362  endif
363
364  if(levdiff2.eq.0) then
365    iwmax=nlev_ec+1
366    do i=0,nxn(l)-1
367      do j=0,nyn(l)-1
368        wwhn(i,j,nlev_ec+1,l)=0.
369      end do
370    end do
371  endif
372
373  do i=0,nxn(l)-1
374    do j=0,nyn(l)-1
375      surfstrn(i,j,1,n,l)=sqrt(ewss(i,j)**2+nsss(i,j)**2)
376    end do
377  end do
378
379  if ((.not.hflswitch).or.(.not.strswitch)) then
380    write(*,*) 'WARNING: No flux data contained in GRIB file ', &
381         wfnamen(l,indj)
382
383  ! CALCULATE USTAR AND SSHF USING THE PROFILE METHOD
384  ! As ECMWF has increased the model resolution, such that now the first model
385  ! level is at about 10 m (where 10-m wind is given), use the 2nd ECMWF level
386  ! (3rd model level in FLEXPART) for the profile method
387  !***************************************************************************
388
389    do i=0,nxn(l)-1
390      do j=0,nyn(l)-1
391        plev1=akz(3)+bkz(3)*psn(i,j,1,n,l)
392        pmean=0.5*(psn(i,j,1,n,l)+plev1)
393        tv=tthn(i,j,3,n,l)*(1.+0.61*qvhn(i,j,3,n,l))
394        fu=-r_air*tv/ga/pmean
395        hlev1=fu*(plev1-psn(i,j,1,n,l))   ! HEIGTH OF FIRST MODEL LAYER
396        ff10m= sqrt(u10n(i,j,1,n,l)**2+v10n(i,j,1,n,l)**2)
397        fflev1=sqrt(uuhn(i,j,3,l)**2+vvhn(i,j,3,l)**2)
398        call pbl_profile(psn(i,j,1,n,l),td2n(i,j,1,n,l),hlev1, &
399             tt2n(i,j,1,n,l),tthn(i,j,3,n,l),ff10m,fflev1, &
400             surfstrn(i,j,1,n,l),sshfn(i,j,1,n,l))
401        if(sshfn(i,j,1,n,l).gt.200.) sshfn(i,j,1,n,l)=200.
402        if(sshfn(i,j,1,n,l).lt.-400.) sshfn(i,j,1,n,l)=-400.
403      end do
404    end do
405  endif
406
407
408  ! Assign 10 m wind to model level at eta=1.0 to have one additional model
409  ! level at the ground
410  ! Specific humidity is taken the same as at one level above
411  ! Temperature is taken as 2 m temperature
412  !**************************************************************************
413
414    do i=0,nxn(l)-1
415      do j=0,nyn(l)-1
416        uuhn(i,j,1,l)=u10n(i,j,1,n,l)
417        vvhn(i,j,1,l)=v10n(i,j,1,n,l)
418        qvhn(i,j,1,n,l)=qvhn(i,j,2,n,l)
419        tthn(i,j,1,n,l)=tt2n(i,j,1,n,l)
420      end do
421    end do
422
423    if(iumax.ne.nuvz-1) stop &
424         'READWIND: NUVZ NOT CONSISTENT FOR A NESTING LEVEL'
425    if(iwmax.ne.nwz) stop &
426         'READWIND: NWZ NOT CONSISTENT FOR A NESTING LEVEL'
427
428  end do
429
430  return
431888   write(*,*) ' #### FLEXPART MODEL ERROR! WINDFIELD         #### '
432  write(*,*) ' #### ',wfnamen(l,indj),' FOR NESTING LEVEL  #### '
433  write(*,*) ' #### ',l,' IS NOT GRIB FORMAT !!!           #### '
434  stop 'Execution terminated'
435
436
437999   write(*,*) ' #### FLEXPART MODEL ERROR! WINDFIELD         #### '
438  write(*,*) ' #### ',wfnamen(l,indj),'                    #### '
439  write(*,*) ' #### CANNOT BE OPENED FOR NESTING LEVEL ',l,'####'
440
441end subroutine readwind_nests
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG