source: flexpart.git/src/readwind_nests.f90 @ 553d0a7

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