source: branches/flexpart91_hasod/src_parallel/readwind_bak.f90 @ 8

Last change on this file since 8 was 8, checked in by hasod, 11 years ago

Added parallel version of Flexpart91

File size: 19.4 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine readwind(indj,n)
23
24  !**********************************************************************
25  !                                                                     *
26  !             TRAJECTORY MODEL SUBROUTINE READWIND                    *
27  !                                                                     *
28  !**********************************************************************
29  !                                                                     *
30  !             AUTHOR:      G. WOTAWA                                  *
31  !             DATE:        1997-08-05                                 *
32  !             LAST UPDATE: 2000-10-17, Andreas Stohl                  *
33  !             CHANGE: 11/01/2008, Harald Sodemann, GRIB1/2 input with *
34  !                                 ECMWF grib_api                      *
35  !             CHANGE: 03/12/2008, Harald Sodemann, update to f90 with *
36  !                                 ECMWF grib_api                      *
37  !                                                                     *
38  !**********************************************************************
39  !  Changes, Bernd C. Krueger, Feb. 2001:
40  !   Variables tth and qvh (on eta coordinates) in common block
41  !**********************************************************************
42  !                                                                     *
43  ! DESCRIPTION:                                                        *
44  !                                                                     *
45  ! READING OF ECMWF METEOROLOGICAL FIELDS FROM INPUT DATA FILES. THE   *
46  ! INPUT DATA FILES ARE EXPECTED TO BE AVAILABLE IN GRIB CODE          *
47  !                                                                     *
48  ! INPUT:                                                              *
49  ! indj               indicates number of the wind field to be read in *
50  ! n                  temporal index for meteorological fields (1 to 3)*
51  !                                                                     *
52  ! IMPORTANT VARIABLES FROM COMMON BLOCK:                              *
53  !                                                                     *
54  ! wfname             File name of data to be read in                  *
55  ! nx,ny,nuvz,nwz     expected field dimensions                        *
56  ! nlev_ec            number of vertical levels ecmwf model            *
57  ! uu,vv,ww           wind fields                                      *
58  ! tt,qv              temperature and specific humidity                *
59  ! ps                 surface pressure                                 *
60  !                                                                     *
61  !**********************************************************************
62
63  use par_mod
64  use com_mod
65  use GRIB_API
66
67  implicit none
68
69  !HSO  parameters for grib_api
70  integer :: ifile
71  integer :: iret
72  integer :: igrib
73  integer :: gribVer,parCat,parNum,typSurf,valSurf,discipl
74  integer :: gotGrid
75  !HSO  end
76
77! real(kind=4) :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
78! real(kind=4) :: vvh(0:nxmax-1,0:nymax-1,nuvzmax)
79! real(kind=4) :: wwh(0:nxmax-1,0:nymax-1,nwzmax)
80  integer :: indj,i,j,k,n,levdiff2,ifield,iumax,iwmax
81
82  ! VARIABLES AND ARRAYS NEEDED FOR GRIB DECODING
83
84  ! dimension of isec2 at least (22+n), where n is the number of parallels or
85  ! meridians in a quasi-regular (reduced) Gaussian or lat/long grid
86
87  ! dimension of zsec2 at least (10+nn), where nn is the number of vertical
88  ! coordinate parameters
89
90  integer :: isec1(56),isec2(22+nxmax+nymax)
91  real(kind=4) :: zsec4(jpunp)
92  real(kind=4) :: xaux,yaux,xaux0,yaux0
93  real(kind=8) :: xauxin,yauxin
94  real,parameter :: eps=1.e-4
95  real(kind=4) :: nsss(0:nxmax-1,0:nymax-1),ewss(0:nxmax-1,0:nymax-1)
96  real :: plev1,pmean,tv,fu,hlev1,ff10m,fflev1
97
98  logical :: hflswitch,strswitch
99
100  !HSO  grib api error messages
101  character(len=24) :: gribErrorMsg = 'Error reading grib file'
102  character(len=20) :: gribFunction = 'readwind'
103
104  !HSO conversion of ECMWF etadot to etadot*dp/deta
105  logical :: etacon=.false.
106  real,parameter :: p00=101325.
107  real :: dak,dbk
108
109  print*,'in readwind'
110  hflswitch=.false.
111  strswitch=.false.
112  levdiff2=nlev_ec-nwz+1
113  iumax=0
114  iwmax=0
115
116  !
117  ! OPENING OF DATA FILE (GRIB CODE)
118  !
119! call grib_open_file(ifile,path(3)(1:length(3)) trim(wfname(indj)),'r',iret)
120  if (iret.ne.GRIB_SUCCESS) then
121    goto 888   ! ERROR DETECTED
122  endif
123  !turn on support for multi fields messages */
124  !call grib_multi_support_on
125
126  gotGrid=0
127  ifield=0
12810   ifield=ifield+1
129  !
130  ! GET NEXT FIELDS
131  !
132  print*,'getting grib data'
133! call grib_new_from_file(ifile,igrib,iret)
134  if (iret.eq.GRIB_END_OF_FILE)  then
135    goto 50    ! EOF DETECTED
136  elseif (iret.ne.GRIB_SUCCESS) then
137    goto 888   ! ERROR DETECTED
138  endif
139
140  !first see if we read GRIB1 or GRIB2
141! call grib_get_int(igrib,'editionNumber',gribVer,iret)
142! call grib_check(iret,gribFunction,gribErrorMsg)
143
144  if (gribVer.eq.1) then ! GRIB Edition 1
145
146  !print*,'GRiB Edition 1'
147  !read the grib2 identifiers
148! call grib_get_int(igrib,'indicatorOfParameter',isec1(6),iret)
149! call grib_check(iret,gribFunction,gribErrorMsg)
150! call grib_get_int(igrib,'level',isec1(8),iret)
151! call grib_check(iret,gribFunction,gribErrorMsg)
152
153  !change code for etadot to code for omega
154  if (isec1(6).eq.77) then
155    isec1(6)=135
156  endif
157
158  else
159
160  !print*,'GRiB Edition 2'
161  !read the grib2 identifiers
162! call grib_get_int(igrib,'discipline',discipl,iret)
163! call grib_check(iret,gribFunction,gribErrorMsg)
164! call grib_get_int(igrib,'parameterCategory',parCat,iret)
165! call grib_check(iret,gribFunction,gribErrorMsg)
166! call grib_get_int(igrib,'parameterNumber',parNum,iret)
167! call grib_check(iret,gribFunction,gribErrorMsg)
168! call grib_get_int(igrib,'typeOfFirstFixedSurface',typSurf,iret)
169! call grib_check(iret,gribFunction,gribErrorMsg)
170! call grib_get_int(igrib,'level',valSurf,iret)
171! call grib_check(iret,gribFunction,gribErrorMsg)
172
173  !print*,discipl,parCat,parNum,typSurf,valSurf
174
175  !convert to grib1 identifiers
176  isec1(6)=-1
177  isec1(7)=-1
178  isec1(8)=-1
179  isec1(8)=valSurf     ! level
180  if ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! T
181    isec1(6)=130         ! indicatorOfParameter
182  elseif ((parCat.eq.2).and.(parNum.eq.2).and.(typSurf.eq.105)) then ! U
183    isec1(6)=131         ! indicatorOfParameter
184  elseif ((parCat.eq.2).and.(parNum.eq.3).and.(typSurf.eq.105)) then ! V
185    isec1(6)=132         ! indicatorOfParameter
186  elseif ((parCat.eq.1).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! Q
187    isec1(6)=133         ! indicatorOfParameter
188  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.1)) then !SP
189    isec1(6)=134         ! indicatorOfParameter
190  elseif ((parCat.eq.2).and.(parNum.eq.32)) then ! W, actually eta dot
191    isec1(6)=135         ! indicatorOfParameter
192  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.101)) then !SLP
193    isec1(6)=151         ! indicatorOfParameter
194  elseif ((parCat.eq.2).and.(parNum.eq.2).and.(typSurf.eq.103)) then ! 10U
195    isec1(6)=165         ! indicatorOfParameter
196  elseif ((parCat.eq.2).and.(parNum.eq.3).and.(typSurf.eq.103)) then ! 10V
197    isec1(6)=166         ! indicatorOfParameter
198  elseif ((parCat.eq.0).and.(parNum.eq.0).and.(typSurf.eq.103)) then ! 2T
199    isec1(6)=167         ! indicatorOfParameter
200  elseif ((parCat.eq.0).and.(parNum.eq.6).and.(typSurf.eq.103)) then ! 2D
201    isec1(6)=168         ! indicatorOfParameter
202  elseif ((parCat.eq.1).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SD
203    isec1(6)=141         ! indicatorOfParameter
204  elseif ((parCat.eq.6).and.(parNum.eq.1)) then ! CC
205    isec1(6)=164         ! indicatorOfParameter
206  elseif ((parCat.eq.1).and.(parNum.eq.9)) then ! LSP
207    isec1(6)=142         ! indicatorOfParameter
208  elseif ((parCat.eq.1).and.(parNum.eq.10)) then ! CP
209    isec1(6)=143         ! indicatorOfParameter
210  elseif ((parCat.eq.0).and.(parNum.eq.11).and.(typSurf.eq.1)) then ! SHF
211    isec1(6)=146         ! indicatorOfParameter
212  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
213    isec1(6)=176         ! indicatorOfParameter
214  elseif ((parCat.eq.2).and.(parNum.eq.17)) then ! EWSS
215    isec1(6)=180         ! indicatorOfParameter
216  elseif ((parCat.eq.2).and.(parNum.eq.18)) then ! NSSS
217    isec1(6)=181         ! indicatorOfParameter
218  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
219    isec1(6)=129         ! indicatorOfParameter
220  elseif ((parCat.eq.3).and.(parNum.eq.7)) then ! SDO
221    isec1(6)=160         ! indicatorOfParameter
222  elseif ((discipl.eq.2).and.(parCat.eq.0).and.(parNum.eq.0).and. &
223       (typSurf.eq.1)) then ! LSM
224    isec1(6)=172         ! indicatorOfParameter
225  else
226    print*,'***ERROR: undefined GRiB2 message found!',discipl, &
227         parCat,parNum,typSurf
228  endif
229
230  endif
231
232  !HSO  get the size and data of the values array
233  if (isec1(6).ne.-1) then
234!   call grib_get_real4_array(igrib,'values',zsec4,iret)
235!   call grib_check(iret,gribFunction,gribErrorMsg)
236  endif
237
238  !HSO  get the required fields from section 2 in a gribex compatible manner
239  if (ifield.eq.1) then
240! call grib_get_int(igrib,'numberOfPointsAlongAParallel', &
241!      isec2(2),iret)
242! call grib_check(iret,gribFunction,gribErrorMsg)
243! call grib_get_int(igrib,'numberOfPointsAlongAMeridian', &
244!      isec2(3),iret)
245! call grib_check(iret,gribFunction,gribErrorMsg)
246! call grib_get_int(igrib,'numberOfVerticalCoordinateValues', &
247!      isec2(12))
248! call grib_check(iret,gribFunction,gribErrorMsg)
249  ! CHECK GRID SPECIFICATIONS
250  if(isec2(2).ne.nxfield) stop 'READWIND: NX NOT CONSISTENT'
251  if(isec2(3).ne.ny) stop 'READWIND: NY NOT CONSISTENT'
252  if(isec2(12)/2-1.ne.nlev_ec) &
253       stop 'READWIND: VERTICAL DISCRETIZATION NOT CONSISTENT'
254  endif ! ifield
255
256  !HSO  get the second part of the grid dimensions only from GRiB1 messages
257  if ((gribVer.eq.1).and.(gotGrid.eq.0)) then
258!   call grib_get_real8(igrib,'longitudeOfFirstGridPointInDegrees', &
259!        xauxin,iret)
260!   call grib_check(iret,gribFunction,gribErrorMsg)
261!   call grib_get_real8(igrib,'latitudeOfLastGridPointInDegrees', &
262!        yauxin,iret)
263!   call grib_check(iret,gribFunction,gribErrorMsg)
264    xaux=xauxin+real(nxshift)*dx
265    yaux=yauxin
266    xaux0=xlon0
267    yaux0=ylat0
268    if(xaux.lt.0.) xaux=xaux+360.
269    if(yaux.lt.0.) yaux=yaux+360.
270    if(xaux0.lt.0.) xaux0=xaux0+360.
271    if(yaux0.lt.0.) yaux0=yaux0+360.
272    if(abs(xaux-xaux0).gt.eps) &
273         stop 'READWIND: LOWER LEFT LONGITUDE NOT CONSISTENT'
274    if(abs(yaux-yaux0).gt.eps) &
275         stop 'READWIND: LOWER LEFT LATITUDE NOT CONSISTENT'
276    gotGrid=1
277  endif ! gotGrid
278
279  do j=0,nymin1
280    do i=0,nxfield-1
281      k=isec1(8)
282      if(isec1(6).eq.130) tth(i,j,nlev_ec-k+2,n)= &!! TEMPERATURE
283           zsec4(nxfield*(ny-j-1)+i+1)
284      if(isec1(6).eq.131) uuh(i,j,nlev_ec-k+2)= &!! U VELOCITY
285           zsec4(nxfield*(ny-j-1)+i+1)
286      if(isec1(6).eq.132) vvh(i,j,nlev_ec-k+2)= &!! V VELOCITY
287           zsec4(nxfield*(ny-j-1)+i+1)
288      if(isec1(6).eq.133) then                      !! SPEC. HUMIDITY
289        qvh(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
290        if (qvh(i,j,nlev_ec-k+2,n) .lt. 0.) &
291             qvh(i,j,nlev_ec-k+2,n) = 0.
292  !        this is necessary because the gridded data may contain
293  !        spurious negative values
294      endif
295      if(isec1(6).eq.134) ps(i,j,1,n)= &!! SURF. PRESS.
296           zsec4(nxfield*(ny-j-1)+i+1)
297
298      if(isec1(6).eq.135) wwh(i,j,nlev_ec-k+1)= &!! W VELOCITY
299           zsec4(nxfield*(ny-j-1)+i+1)
300      if(isec1(6).eq.141) sd(i,j,1,n)= &!! SNOW DEPTH
301           zsec4(nxfield*(ny-j-1)+i+1)
302      if(isec1(6).eq.151) msl(i,j,1,n)= &!! SEA LEVEL PRESS.
303           zsec4(nxfield*(ny-j-1)+i+1)
304      if(isec1(6).eq.164) tcc(i,j,1,n)= &!! CLOUD COVER
305           zsec4(nxfield*(ny-j-1)+i+1)
306      if(isec1(6).eq.165) u10(i,j,1,n)= &!! 10 M U VELOCITY
307           zsec4(nxfield*(ny-j-1)+i+1)
308      if(isec1(6).eq.166) v10(i,j,1,n)= &!! 10 M V VELOCITY
309           zsec4(nxfield*(ny-j-1)+i+1)
310      if(isec1(6).eq.167) tt2(i,j,1,n)= &!! 2 M TEMPERATURE
311           zsec4(nxfield*(ny-j-1)+i+1)
312      if(isec1(6).eq.168) td2(i,j,1,n)= &!! 2 M DEW POINT
313           zsec4(nxfield*(ny-j-1)+i+1)
314      if(isec1(6).eq.142) then                      !! LARGE SCALE PREC.
315        lsprec(i,j,1,n)=zsec4(nxfield*(ny-j-1)+i+1)
316        if (lsprec(i,j,1,n).lt.0.) lsprec(i,j,1,n)=0.
317      endif
318      if(isec1(6).eq.143) then                      !! CONVECTIVE PREC.
319        convprec(i,j,1,n)=zsec4(nxfield*(ny-j-1)+i+1)
320        if (convprec(i,j,1,n).lt.0.) convprec(i,j,1,n)=0.
321      endif
322      if(isec1(6).eq.146) sshf(i,j,1,n)= &!! SENS. HEAT FLUX
323           zsec4(nxfield*(ny-j-1)+i+1)
324      if((isec1(6).eq.146).and.(zsec4(nxfield*(ny-j-1)+i+1).ne.0.)) &
325           hflswitch=.true.    ! Heat flux available
326      if(isec1(6).eq.176) then                      !! SOLAR RADIATION
327        ssr(i,j,1,n)=zsec4(nxfield*(ny-j-1)+i+1)
328        if (ssr(i,j,1,n).lt.0.) ssr(i,j,1,n)=0.
329      endif
330      if(isec1(6).eq.180) ewss(i,j)= &!! EW SURFACE STRESS
331           zsec4(nxfield*(ny-j-1)+i+1)
332      if(isec1(6).eq.181) nsss(i,j)= &!! NS SURFACE STRESS
333           zsec4(nxfield*(ny-j-1)+i+1)
334      if(((isec1(6).eq.180).or.(isec1(6).eq.181)).and. &
335           (zsec4(nxfield*(ny-j-1)+i+1).ne.0.)) strswitch=.true.    ! stress available
336  !sec        strswitch=.true.
337      if(isec1(6).eq.129) oro(i,j)= &!! ECMWF OROGRAPHY
338           zsec4(nxfield*(ny-j-1)+i+1)/ga
339      if(isec1(6).eq.160) excessoro(i,j)= &!! STANDARD DEVIATION OF OROGRAPHY
340           zsec4(nxfield*(ny-j-1)+i+1)
341      if(isec1(6).eq.172) lsm(i,j)= &!! ECMWF LAND SEA MASK
342           zsec4(nxfield*(ny-j-1)+i+1)
343      if(isec1(6).eq.131) iumax=max(iumax,nlev_ec-k+1)
344      if(isec1(6).eq.135) iwmax=max(iwmax,nlev_ec-k+1)
345
346    end do
347  end do
348
349! call grib_release(igrib)
350  goto 10                      !! READ NEXT LEVEL OR PARAMETER
351  !
352  ! CLOSING OF INPUT DATA FILE
353  !
35450   continue
355     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,nxmin1
367      do j=0,nymin1
368        wwh(i,j,nlev_ec+1)=0.
369      end do
370    end do
371  endif
372
373  ! convert from ECMWF etadot to etadot*dp/deta as needed by FLEXPART
374  if(etacon.eqv..true.) then
375    do k=1,nwzmax
376      dak=akm(k+1)-akm(k)
377      dbk=bkm(k+1)-bkm(k)
378      do i=0,nxmin1
379        do j=0,nymin1
380          wwh(i,j,k)=2*wwh(i,j,k)*ps(i,j,1,n)*(dak/ps(i,j,1,n)+dbk)/(dak/p00+dbk)
381          if (k.gt.1) then
382            wwh(i,j,k)=wwh(i,j,k)-wwh(i,j,k-1)
383          endif
384        end do
385      end do
386    end do
387  endif
388
389  ! For global fields, assign the leftmost data column also to the rightmost
390  ! data column; if required, shift whole grid by nxshift grid points
391  !*************************************************************************
392
393  if (xglobal) then
394    call shift_field_0(ewss,nxfield,ny)
395    call shift_field_0(nsss,nxfield,ny)
396    call shift_field_0(oro,nxfield,ny)
397    call shift_field_0(excessoro,nxfield,ny)
398    call shift_field_0(lsm,nxfield,ny)
399    call shift_field(ps,nxfield,ny,1,1,2,n)
400    call shift_field(sd,nxfield,ny,1,1,2,n)
401    call shift_field(msl,nxfield,ny,1,1,2,n)
402    call shift_field(tcc,nxfield,ny,1,1,2,n)
403    call shift_field(u10,nxfield,ny,1,1,2,n)
404    call shift_field(v10,nxfield,ny,1,1,2,n)
405    call shift_field(tt2,nxfield,ny,1,1,2,n)
406    call shift_field(td2,nxfield,ny,1,1,2,n)
407    call shift_field(lsprec,nxfield,ny,1,1,2,n)
408    call shift_field(convprec,nxfield,ny,1,1,2,n)
409    call shift_field(sshf,nxfield,ny,1,1,2,n)
410    call shift_field(ssr,nxfield,ny,1,1,2,n)
411    call shift_field(tth,nxfield,ny,nuvzmax,nuvz,2,n)
412    call shift_field(qvh,nxfield,ny,nuvzmax,nuvz,2,n)
413    call shift_field(uuh,nxfield,ny,nuvzmax,nuvz,1,1)
414    call shift_field(vvh,nxfield,ny,nuvzmax,nuvz,1,1)
415    call shift_field(wwh,nxfield,ny,nwzmax,nwz,1,1)
416  endif
417
418  do i=0,nxmin1
419    do j=0,nymin1
420      surfstr(i,j,1,n)=sqrt(ewss(i,j)**2+nsss(i,j)**2)
421    end do
422  end do
423
424  if ((.not.hflswitch).or.(.not.strswitch)) then
425    write(*,*) 'WARNING: No flux data contained in GRIB file ', &
426         wfname(indj)
427
428  ! CALCULATE USTAR AND SSHF USING THE PROFILE METHOD
429  ! As ECMWF has increased the model resolution, such that now the first model
430  ! level is at about 10 m (where 10-m wind is given), use the 2nd ECMWF level
431  ! (3rd model level in FLEXPART) for the profile method
432  !***************************************************************************
433
434    do i=0,nxmin1
435      do j=0,nymin1
436        plev1=akz(3)+bkz(3)*ps(i,j,1,n)
437        pmean=0.5*(ps(i,j,1,n)+plev1)
438        tv=tth(i,j,3,n)*(1.+0.61*qvh(i,j,3,n))
439        fu=-r_air*tv/ga/pmean
440        hlev1=fu*(plev1-ps(i,j,1,n))   ! HEIGTH OF FIRST MODEL LAYER
441        ff10m= sqrt(u10(i,j,1,n)**2+v10(i,j,1,n)**2)
442        fflev1=sqrt(uuh(i,j,3)**2+vvh(i,j,3)**2)
443        call pbl_profile(ps(i,j,1,n),td2(i,j,1,n),hlev1, &
444             tt2(i,j,1,n),tth(i,j,3,n),ff10m,fflev1, &
445             surfstr(i,j,1,n),sshf(i,j,1,n))
446        if(sshf(i,j,1,n).gt.200.) sshf(i,j,1,n)=200.
447        if(sshf(i,j,1,n).lt.-400.) sshf(i,j,1,n)=-400.
448      end do
449    end do
450  endif
451
452
453  ! Assign 10 m wind to model level at eta=1.0 to have one additional model
454  ! level at the ground
455  ! Specific humidity is taken the same as at one level above
456  ! Temperature is taken as 2 m temperature
457  !**************************************************************************
458
459     do i=0,nxmin1
460        do j=0,nymin1
461           uuh(i,j,1)=u10(i,j,1,n)
462           vvh(i,j,1)=v10(i,j,1,n)
463           qvh(i,j,1,n)=qvh(i,j,2,n)
464           tth(i,j,1,n)=tt2(i,j,1,n)
465        end do
466     end do
467
468  if(iumax.ne.nuvz-1) stop 'READWIND: NUVZ NOT CONSISTENT'
469  if(iwmax.ne.nwz)    stop 'READWIND: NWZ NOT CONSISTENT'
470
471  return
472888   write(*,*) ' #### FLEXPART MODEL ERROR! WINDFIELD         #### '
473  write(*,*) ' #### ',wfname(indj),'                    #### '
474  write(*,*) ' #### IS NOT GRIB FORMAT !!!                  #### '
475  stop 'Execution terminated'
476999   write(*,*) ' #### FLEXPART MODEL ERROR! WINDFIELD         #### '
477  write(*,*) ' #### ',wfname(indj),'                    #### '
478  write(*,*) ' #### CANNOT BE OPENED !!!                    #### '
479  stop 'Execution terminated'
480
481end subroutine readwind
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG