Subversion Repositories lagranto.ecmwf

Rev

Rev 44 | Show entire file | Ignore whitespace | Details | Blame | Last modification | View Log | RSS feed

Rev 44 Rev 46
Line 258... Line 258...
258
    tstart = tst
258
    tstart = tst
259
  endif
259
  endif
260
 
260
 
261
  ! Read the constant grid parameters (nx,ny,nz,xmin,xmax,ymin,ymax,pollon,pollat)
261
  ! Read the constant grid parameters (nx,ny,nz,xmin,xmax,ymin,ymax,pollon,pollat)
262
  ! The negative <-fid> of the file identifier is used as a flag for parameter retrieval
262
  ! The negative <-fid> of the file identifier is used as a flag for parameter retrieval
263
  filename = charp//dat(1)
263
 filename = charp//dat(1)
264
  varname  = 'U'
264
  varname  = 'nil'
-
 
265
  do i=1,n_pvars
-
 
266
     if ( (pvars(i).eq.'U').and.(varname.eq.'nil') ) varname  = 'U'
-
 
267
     if ( (pvars(i).eq.'T').and.(varname.eq.'nil') ) varname  = 'T'
-
 
268
  enddo
-
 
269
  if ( varname.eq.'nil' ) varname = tvar(1)
265
  call input_open (fid,filename)
270
  call input_open (fid,filename)
266
  call input_grid (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,tstart,pollon,pollat,rd,rd,nz,rd,rd,rd,timecheck)
271
  call input_grid (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,tstart,pollon,pollat,rd,rd,nz,rd,rd,rd,timecheck)
267
  call input_close(fid)
272
  call input_close(fid)
-
 
273
  if ( nz.eq.1 ) then
-
 
274
     print*,' ERROR: the first tracing variable must be 3D'
-
 
275
     stop
-
 
276
  endif
-
 
277
 
-
 
278
 
-
 
279
 ! filename = charp//dat(1)
-
 
280
 ! varname  = 'U'
-
 
281
 ! call input_open (fid,filename)
-
 
282
 ! call input_grid (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,tstart,pollon,pollat,rd,rd,nz,rd,rd,rd,timecheck)
-
 
283
 ! call input_close(fid)
268
 
284
 
269
  ! Allocate memory for some meteorological arrays
285
  ! Allocate memory for some meteorological arrays
270
  allocate(spt0(nx*ny),stat=stat)
286
  allocate(spt0(nx*ny),stat=stat)
271
  if (stat.ne.0) print*,'*** error allocating array spt0 ***'   ! Surface pressure
287
  if (stat.ne.0) print*,'*** error allocating array spt0 ***'   ! Surface pressure
272
  allocate(spt1(nx*ny),stat=stat)
288
  allocate(spt1(nx*ny),stat=stat)