Subversion Repositories lagranto.ocean

Rev

Details | Last modification | View Log | RSS feed

Rev Author Line No. Line
3 michaesp 1
PROGRAM trace
2
 
3
  ! ********************************************************************
4
  ! *                                                                  *
5
  ! * Trace fields along trajectories                                  *
6
  ! *                                                                  *
7
  ! * April 1993: First version (Heini Wernli)                         *
8
  ! * 2008-2009 : Major upgrades (Michael Sprenger)                    *
9
  ! * Mar 2012: Clustering option (Bojan Skerlak)                      *  
10
  ! * Nov 2012: Circle options (")                                     *
11
  ! * Jul 2013: user-defined PV,TH @ clustering mode (")               *
12
  ! *                                                                  *
13
  ! ********************************************************************
14
 
15
  implicit none
16
 
17
  ! --------------------------------------------------------------------
18
  ! Declaration of parameters
19
  ! --------------------------------------------------------------------
20
 
21
  ! Maximum number of levels for input files
22
  integer :: nlevmax
23
  parameter (nlevmax=100)
24
 
25
  ! Maximum number of input files (dates, length of trajectories)
26
  integer :: ndatmax
27
  parameter (ndatmax=500)
28
 
29
  ! Numerical epsilon (for float comparison)
30
  real :: eps
31
  parameter (eps=0.001)
32
 
33
  ! Conversion factors
34
  real :: pi180                                   ! deg -> rad
35
  parameter (pi180=3.14159/180.)
36
  real :: deg2km                                  ! deg -> km (at equator)
37
  parameter (deg2km=111.)
38
  real :: pir
39
  parameter (pir=255032235.95489)                 ! 2*Pi*R^2 Bojan
40
 
41
  ! Prefix for primary and secondary fields
42
  character :: charp
43
  character :: chars
44
  parameter (charp='P')
45
  parameter (chars='S')
46
 
47
  ! --------------------------------------------------------------------
48
  ! Declaration of variables
49
  ! --------------------------------------------------------------------
50
 
51
  ! Input and output format for trajectories (see iotra.f)
52
  integer :: inpmode
53
  integer :: outmode
54
 
55
  ! Input parameters
56
  character(len=80) :: inpfile         ! Input trajectory file
57
  character(len=80) :: outfile         ! Output trajectory file
58
  integer :: ntra                      ! Number of trajectories
59
  integer :: ncol                      ! Number of columns (including time, lon, lat, p)
60
  integer :: ntim                      ! Number of times per trajectory
61
  integer :: ntrace0                   ! Number of trace variables
62
  character(len=80) :: tvar0(200)      ! Tracing variable (with mode specification)
63
  character(len=80) :: tvar(200)       ! Tracing variable name (only the variable)
64
  character(len=1)  :: tfil(200)       ! Filename prefix
65
  real :: fac(200)                     ! Scaling factor
66
  real :: shift_val(200)               ! Shift in space and time relative to trajectory position
67
  character(len=80) :: shift_dir(200)  ! Direction of shift
68
  integer :: compfl(200)               ! Computation flag (1=compute)
69
  integer :: numdat                    ! Number of input files
70
  character(len=11) :: dat(ndatmax)    ! Dates of input files
71
  real :: timeinc                      ! Time increment between input files
72
  real :: tst                          ! Time shift of start relative to first data file
73
  real :: ten                          ! Time shift of end relatiev to first data file
74
  character(len=20) :: startdate       ! First time/date on trajectory
75
  character(len=20) :: enddate         ! Last time/date on trajectory
76
  integer :: ntrace1                   ! Count trace and additional variables
77
  character(len=80) :: timecheck       ! Either 'yes' or 'no'
78
  character(len=80) :: intmode         ! Interpolation mode ('normal', 'nearest') Bojan ('clustering','circle_avg','circle_max','circle_min')
79
 
80
  ! Trajectories
81
  real,allocatable, dimension (:,:,:) :: trainp          ! Input trajectories (ntra,ntim,ncol)
82
  real,allocatable, dimension (:,:,:) :: traint          ! Internal trajectories (ntra,ntim,ncol+ntrace1)
83
  real,allocatable, dimension (:,:,:) :: traout          ! Output trajectories (ntra,ntim,ncol+ntrace0)
84
  integer :: reftime(6)                                  ! Reference date
85
  character(len=80) :: varsinp(200)                      ! Field names for input trajectory
86
  character(len=80) :: varsint(200)                      ! Field names for internal trajectory
87
  character(len=80) :: varsout(200)                      ! Field names for output trajectory
88
  integer :: fid,fod                                     ! File identifier for inp and out trajectories
89
  real :: x0,y0,p0                                       ! Position of air parcel (physical space)
90
  real :: reltpos0                                       ! Relative time of air parcel
91
  real :: xind,yind,pind                                 ! Position of air parcel (grid space)
92
  integer :: fbflag                                      ! Flag for forward (1) or backward (-1) trajectories
93
  integer :: fok(200)                                    ! Flag whether field is ready
94
 
95
  ! Meteorological fields
96
  real,allocatable, dimension (:)     :: spt0,spt1       ! Surface pressure
97
  real,allocatable, dimension (:)     :: p3t0,p3t1       ! 3d-pressure
98
  real,allocatable, dimension (:)     :: f3t0,f3t1       ! 3d field for tracing
99
  character(len=80) :: svars(100)                        ! List of variables on S file
100
  character(len=80) :: pvars(100)                        ! List of variables on P file
101
  integer :: n_svars                                     ! Number of variables on S file
102
  integer :: n_pvars                                     ! Number of variables on P file
103
 
104
  ! Grid description
105
  real :: pollon,pollat   ! Longitude/latitude of pole
106
  real :: ak(100)         ! Vertical layers and levels
107
  real :: bk(100)
108
  real :: xmin,xmax       ! Zonal grid extension
109
  real :: ymin,ymax       ! Meridional grid extension
110
  integer :: nx,ny,nz     ! Grid dimensions
111
  real :: dx,dy           ! Horizontal grid resolution
112
  integer :: hem          ! Flag for hemispheric domain
113
  integer :: per          ! Flag for periodic domain
114
  real :: stagz           ! Vertical staggering
115
  real :: mdv             ! Missing data value
116
 
117
  ! Auxiliary variables
118
  integer :: i,j,k,l,m,n
119
  real :: rd
120
  character(len=80) :: filename,varname
121
  real :: time0,time1,reltpos
122
  integer :: itime0,itime1
123
  integer :: stat
124
  real :: tstart
125
  integer :: iloaded0,iloaded1
126
  real :: f0
127
  real :: frac
128
  real :: tload,tfrac
129
  integer :: isok
130
  character :: ch
131
  integer :: ind
132
  integer :: ind1,ind2,ind3,ind4,ind5
133
  integer :: ind6,ind7,ind8,ind9,ind0
134
  integer :: noutside
135
  real :: delta
136
  integer :: itrace0
137
  character(len=80) :: string
138
  integer err_c1,err_c2,err_c3
139
 
140
  ! Bojan
141
  real    :: dist,circlesum,circlemax,circlemin,circleavg,radius       ! distance (great circle), sum/max/min/avg in circle, radius of circle
142
  integer :: ist,jst,kst,sp,ml,mr,nd,nu                                ! ijk in stack, sp=stack counter, ml (left), mr (right), nd (down), nu (up)
143
  integer :: lci,lcj,xindb,xindf                                       ! label count i and j, xind back, xind forward
144
  integer :: yindb,yindf,pindb,pindf                                   ! yind back, yind forward, pind back, pind forward
145
  integer :: pvpos,thpos                                               ! position of variables PV and TH in trajectory
146
  real    :: tropo_pv,tropo_th                                         ! values of PV and TH at dynamical tropopause
147
  integer, allocatable, dimension (:)   :: stackx,stacky               ! lon/lat of stack
148
  integer, allocatable, dimension (:)   :: lblcount                    ! counter for label
149
  integer, allocatable, dimension (:,:) :: connect                     ! array that keeps track of the visited grid points
150
  real, allocatable, dimension (:)      :: lbl                         ! label
151
  real, allocatable, dimension (:)      :: circlelon,circlelat         ! value of f, lon and lat in circle
152
  real, allocatable, dimension (:)      :: circlef,circlearea          ! value of f, lon and lat in circle
153
  real, allocatable, dimension (:)      :: longrid,latgrid             ! arrays of longitude and latitude of grid points
154
  ! Bojan
155
 
156
  ! Externals
157
  real :: int_index4
158
  external                               int_index4
159
  real :: sdis ! Bojan: need function sdis (calculates great circle distance)
160
  external                               sdis ! Bojan: need function sdis
161
 
162
  ! --------------------------------------------------------------------
163
  ! Start of program, Read parameters, get grid parameters
164
  ! --------------------------------------------------------------------
165
 
166
  ! Write start message
167
  print*,'========================================================='
168
  print*,'              *** START OF PROGRAM TRACE ***'
169
  print*
170
 
171
  ! Read parameters
172
  open(10,file='trace.param')
173
   read(10,*) inpfile
174
   read(10,*) outfile
175
   read(10,*) startdate
176
   read(10,*) enddate
177
   read(10,*) fbflag
178
   read(10,*) numdat
179
   if ( fbflag.eq.1) then
180
      do i=1,numdat
181
         read(10,'(a11)') dat(i)
182
      enddo
183
   else
184
      do i=numdat,1,-1
185
         read(10,'(a11)') dat(i)
186
      enddo
187
   endif
188
   read(10,*) timeinc
189
   read(10,*) tst
190
   read(10,*) ten
191
   read(10,*) ntra
192
   read(10,*) ntim
193
   read(10,*) ncol
194
   read(10,*) ntrace0
195
   do i=1,ntrace0
196
      read(10,*) tvar(i), fac(i), compfl(i), tfil(i)
197
   enddo
198
   read(10,*) n_pvars
199
   do i=1,n_pvars
200
      read(10,*) pvars(i)
201
   enddo
202
   read(10,*) n_svars
203
   do i=1,n_svars
204
      read(10,*) svars(i)
205
   enddo
206
   read(10,*) timecheck
207
   read(10,*) intmode
208
   read(10,*) radius
209
   read(10,*) tropo_pv
210
   read(10,*) tropo_th
211
  close(10)
212
 
213
  ! Bojan: error if radius < 0
214
  if (((intmode .eq. "circle_avg") .or. (intmode .eq. "circle_min") .or. (intmode .eq. "circle_max")) .and. (radius .lt. 0)) then
215
     print*,'ERROR (circle): radius < 0!'
216
     stop
217
  endif
218
 
219
  ! Remove commented tracing fields
220
  itrace0 = 1
221
  do while ( itrace0.le.ntrace0)
222
     string = tvar(itrace0)
223
     if ( string(1:1).eq.'#' ) then
224
        do i=itrace0,ntrace0-1
225
           tvar(i)   = tvar(i+1)
226
           fac(i)    = fac(i+1)
227
           compfl(i) = compfl(i+1)
228
           tfil(i)   = tfil(i+1)
229
        enddo
230
        ntrace0 = ntrace0 - 1
231
     else
232
        itrace0 = itrace0 + 1
233
     endif
234
  enddo
235
 
236
  ! Save the tracing variable (including all mode specifications)
237
  do i=1,ntrace0
238
     tvar0(i) = tvar(i)
239
  enddo
240
 
241
  ! Set the formats of the input and output files
242
  call mode_tra(inpmode,inpfile)
243
  if (inpmode.eq.-1) inpmode=1
244
  call mode_tra(outmode,outfile)
245
  if (outmode.eq.-1) outmode=1
246
 
247
  ! Convert time shifts <tst,ten> from <hh.mm> into fractional time
248
  call hhmm2frac(tst,frac)
249
  tst = frac
250
  call hhmm2frac(ten,frac)
251
  ten = frac
252
 
253
  ! Set the time for the first data file (depending on forward/backward mode)
254
  if (fbflag.eq.1) then
255
    tstart = -tst
256
  else
257
    tstart = tst
258
  endif
259
 
260
  ! Read the constant grid parameters (nx,ny,nz,xmin,xmax,ymin,ymax,pollon,pollat)
261
  ! The negative <-fid> of the file identifier is used as a flag for parameter retrieval
262
  filename = charp//dat(1)
263
  varname  = 'U'
264
  call input_open (fid,filename)
265
  call input_grid (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,tstart,pollon,pollat,rd,rd,nz,rd,timecheck)
266
  call input_close(fid)
267
 
268
  ! Allocate memory for some meteorological arrays
269
  allocate(spt0(nx*ny),stat=stat)
270
  if (stat.ne.0) print*,'*** error allocating array spt0 ***'   ! Surface pressure
271
  allocate(spt1(nx*ny),stat=stat)
272
  if (stat.ne.0) print*,'*** error allocating array spt1 ***'
273
  allocate(p3t0(nx*ny*nz),stat=stat)
274
  if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Pressure
275
  allocate(p3t1(nx*ny*nz),stat=stat)
276
  if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
277
  allocate(f3t0(nx*ny*nz),stat=stat)
278
  if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Tracing field
279
  allocate(f3t1(nx*ny*nz),stat=stat)
280
  if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
281
 
282
  ! Get memory for trajectory arrays
283
  allocate(trainp(ntra,ntim,ncol),stat=stat)
284
  if (stat.ne.0) print*,'*** error allocating array tra      ***'
285
 
286
  ! Bojan
287
  ! allocate memory for clustering mode 
288
  if (intmode .eq. 'clustering') then
289
     allocate(lbl(8),stat=stat)
290
     if (stat.ne.0) print*,'*** error allocating array lbl      ***'
291
     allocate(lblcount(5),stat=stat)
292
     if (stat.ne.0) print*,'*** error allocating array lblcount ***'
293
  endif
294
  ! allocate memory for circle mode
295
  if ( (intmode.eq.'circle_avg') .or. (intmode.eq.'circle_min') .or. (intmode.eq.'circle_max') ) then
296
     allocate(connect(nx,ny),stat=stat)
297
     if (stat.ne.0) print*,'*** error allocating connect ***'
298
     allocate(stackx(nx*ny),stat=stat)
299
     if (stat.ne.0) print*,'*** error allocating stackx ***'
300
     allocate(stacky(nx*ny),stat=stat)
301
     if (stat.ne.0) print*,'*** error allocating stacky ***'
302
     allocate(circlelon(nx*ny),stat=stat)
303
     if (stat.ne.0) print*,'*** error allocating circlelon ***'
304
     allocate(circlelat(nx*ny),stat=stat)
305
     if (stat.ne.0) print*,'*** error allocating circlelat ***'
306
     allocate(circlef(nx*ny),stat=stat)
307
     if (stat.ne.0) print*,'*** error allocating circlef ***'
308
     allocate(circlearea(nx*ny),stat=stat)
309
     if (stat.ne.0) print*,'*** error allocating circlearea ***'
310
     allocate(longrid(nx),stat=stat)
311
     if (stat.ne.0) print*,'*** error allocating longrid ***'
312
     allocate(latgrid(ny),stat=stat)
313
     if (stat.ne.0) print*,'*** error allocating latgrid ***'
314
     do m=1,nx
315
        longrid(m)=xmin+dx*(m-1)
316
     enddo
317
     do n=1,ny
318
        latgrid(n)=ymin+dy*(n-1)
319
     enddo
320
  endif
321
  ! Bojan
322
 
323
  ! Set the flags for periodic domains
324
  if ( abs(xmax-xmin-360.).lt.eps ) then
325
     per = 1
326
  elseif ( abs(xmax-xmin-360.+dx).lt.eps ) then
327
     per = 2
328
  else
329
     per = 0
330
  endif
331
 
332
  ! Set logical flag for periodic data set (hemispheric or not)
333
  hem = 0
334
  if (per.eq.0.) then
335
     delta=xmax-xmin-360.
336
     if (abs(delta+dx).lt.eps) then               ! Program aborts: arrays must be closed
337
        print*,' ERROR: arrays must be closed... Stop'
338
     else if (abs(delta).lt.eps) then ! Periodic and hemispheric
339
       hem=1
340
       per=360.
341
    endif
342
  else                                            ! Periodic and hemispheric
343
     hem=1
344
  endif
345
 
346
  ! Write some status information
347
  print*,'---- INPUT PARAMETERS -----------------------------------'
348
  print*
349
  print*,'  Input trajectory file  : ',trim(inpfile)
350
  print*,'  Output trajectory file : ',trim(outfile)
351
  print*,'  Format of input file   : ',inpmode
352
  print*,'  Format of output file  : ',outmode
353
  print*,'  Forward/backward       : ',fbflag
354
  print*,'  #tra                   : ',ntra
355
  print*,'  #col                   : ',ncol
356
  print*,'  #tim                   : ',ntim
357
  print*,'  No time check          : ',trim(timecheck)
358
  print*,'  Interpolation mode     : ',trim(intmode)
359
  ! Bojan
360
  if (trim(intmode) .eq. "clustering") then
361
     print*,'  Tropopause PV [pvu]    : ',tropo_pv
362
     print*,'  Tropopause TH [K]      : ',tropo_th
363
  endif
364
  do i=1,ntrace0
365
     if (compfl(i).eq.0) then
366
        print*,'  Tracing field          : ', trim(tvar(i)), fac(i), ' 0 ', tfil(i)
367
     else
368
        print*,'  Tracing field          : ', trim(tvar(i)), fac(i), '  1 ', tfil(i)
369
     endif
370
  enddo
371
  print*
372
  print*,'---- INPUT DATA FILES -----------------------------------'
373
  print*
374
  call frac2hhmm(tstart,tload)
375
  print*,'  Time of 1st data file  : ',tload
376
  print*,'  #input files           : ',numdat
377
  print*,'  time increment         : ',timeinc
378
  call frac2hhmm(tst,tload)
379
  print*,'  Shift of start         : ',tload
380
  call frac2hhmm(ten,tload)
381
  print*,'  Shift of end           : ',tload
382
  print*,'  First/last input file  : ',trim(dat(1)), ' ... ', trim(dat(numdat))
383
  print*,'  Primary variables      : ',trim(pvars(1))
384
  do i=2,n_pvars
385
     print*,'                         : ',trim(pvars(i))
386
  enddo
387
  if ( n_svars.ge.1 ) then
388
     print*,'  Secondary variables    : ',trim(svars(1))
389
     do i=2,n_svars
390
        print*,'                         : ',trim(svars(i))
391
     enddo
392
  endif
393
  print*
394
  print*,'---- CONSTANT GRID PARAMETERS ---------------------------'
395
  print*
396
  print*,'  xmin,xmax     : ',xmin,xmax
397
  print*,'  ymin,ymax     : ',ymin,ymax
398
  print*,'  dx,dy         : ',dx,dy
399
  print*,'  pollon,pollat : ',pollon,pollat
400
  print*,'  nx,ny,nz      : ',nx,ny,nz
401
  print*,'  per, hem      : ',per,hem
402
  print*
403
 
404
  ! --------------------------------------------------------------------
405
  ! Load the input trajectories
406
  ! --------------------------------------------------------------------
407
 
408
  ! Read the input trajectory file
409
  call ropen_tra(fid,inpfile,ntra,ntim,ncol,reftime,varsinp,inpmode)
410
  call read_tra (fid,trainp,ntra,ntim,ncol,inpmode)
411
  call close_tra(fid,inpmode)
412
 
413
  ! Check that first four columns correspond to time,lon,lat,p
414
  if ( (varsinp(1).ne.'time' ).or. &
415
       (varsinp(2).ne.'xpos' ).and.(varsinp(2).ne.'lon' ).or. &
416
       (varsinp(3).ne.'ypos' ).and.(varsinp(3).ne.'lat' ).or. &
417
       (varsinp(4).ne.'zpos' ).and.(varsinp(4).ne.'depth'   ) ) then
418
     print*,' ERROR: problem with input trajectories ...'
419
     stop
420
  endif
421
  varsinp(1) = 'time'
422
  varsinp(2) = 'lon'
423
  varsinp(3) = 'lat'
424
  varsinp(4) = 'depth'
425
 
426
  ! Write some status information of the input trajectories
427
  print*,'---- INPUT TRAJECTORIES ---------------------------------'
428
  print*
429
  print*,' Start date             : ',trim(startdate)
430
  print*,' End date               : ',trim(enddate)
431
  print*,' Reference time (year)  : ',reftime(1)
432
  print*,'                (month) : ',reftime(2)
433
  print*,'                (day)   : ',reftime(3)
434
  print*,'                (hour)  : ',reftime(4)
435
  print*,'                (min)   : ',reftime(5)
436
  print*,' Time range (min)       : ',reftime(6)
437
  do i=1,ncol
438
     print*,' Var                    :',i,trim(varsinp(i))
439
  enddo
440
  print*
441
 
442
  ! Check that first time is 0 - otherwise the tracing will produce
443
  ! wrong results because later in the code only absolute times are
444
  ! considered: <itime0   = int(abs(tfrac-tstart)/timeinc) + 1>. This
445
  ! will be changed in a future version.
446
  if ( abs( trainp(1,1,1) ).gt.eps ) then
447
     print*,' ERROR: First time of trajectory must be 0, i.e. '
448
     print*,'     correspond to the reference date. Otherwise'
449
     print*,'     the tracing will give wrong results... STOP'
450
     stop
451
  endif
452
 
453
  ! --------------------------------------------------------------------
454
  ! Check dependencies for trace fields which must be calculated
455
  ! --------------------------------------------------------------------
456
 
457
  ! Set the counter for extra fields
458
  ntrace1 = ntrace0
459
 
460
  ! Loop over all tracing variables
461
  i = 1
462
  do while (i.le.ntrace1)
463
 
464
     ! Skip fields which must be available on the input files
465
     if (i.le.ntrace0) then
466
        if (compfl(i).eq.0) goto 100
467
     endif
468
 
469
     ! Get the dependencies for potential temperature (TH)
470
     if ( tvar(i).eq.'TH' ) then
471
        varname='P'                                   ! P
472
        call add2list(varname,tvar,ntrace1)
473
        varname='T'                                   ! T
474
        call add2list(varname,tvar,ntrace1)
475
 
476
     ! Get the dependencies for potential temperature (TH)
477
     elseif ( tvar(i).eq.'RHO' ) then
478
        varname='P'                                   ! P
479
        call add2list(varname,tvar,ntrace1)
480
        varname='T'                                   ! T
481
        call add2list(varname,tvar,ntrace1)
482
 
483
     ! Get the dependencies for relative humidity (RH)
484
     elseif ( tvar(i).eq.'RH' ) then
485
        varname='P'                                   ! P
486
        call add2list(varname,tvar,ntrace1)
487
        varname='T'                                   ! T
488
        call add2list(varname,tvar,ntrace1)
489
        varname='Q'                                   ! Q
490
        call add2list(varname,tvar,ntrace1)
491
 
492
     ! Get the dependencies for equivalent potential temperature (THE)
493
     elseif ( tvar(i).eq.'THE' ) then
494
        varname='P'                                   ! P
495
        call add2list(varname,tvar,ntrace1)
496
        varname='T'                                   ! T
497
        call add2list(varname,tvar,ntrace1)
498
        varname='Q'                                   ! Q
499
        call add2list(varname,tvar,ntrace1)
500
 
501
     ! Get the dependencies for latent heating rate (LHR)
502
     elseif ( tvar(i).eq.'LHR' ) then
503
        varname='P'                                   ! P
504
        call add2list(varname,tvar,ntrace1)
505
        varname='T'                                   ! T
506
        call add2list(varname,tvar,ntrace1)
507
        varname='Q'                                   ! Q
508
        call add2list(varname,tvar,ntrace1)
509
        varname='OMEGA'                               ! OMEGA
510
        call add2list(varname,tvar,ntrace1)
511
        varname='RH'                                  ! RH
512
        call add2list(varname,tvar,ntrace1)
513
 
514
     ! Get the dependencies for wind speed (VEL)
515
     elseif ( tvar(i).eq.'VEL' ) then
516
        varname='U'                                   ! U
517
        call add2list(varname,tvar,ntrace1)
518
        varname='V'                                   ! V
519
        call add2list(varname,tvar,ntrace1)
520
 
521
     ! Get the dependencies for wind direction (DIR)
522
     elseif ( tvar(i).eq.'DIR' ) then
523
        varname='U'                                   ! U
524
        call add2list(varname,tvar,ntrace1)
525
        varname='V'                                   ! V
526
        call add2list(varname,tvar,ntrace1)
527
 
528
     ! Get the dependencies for du/dx (DUDX)
529
     elseif ( tvar(i).eq.'DUDX' ) then
530
        varname='U:+1DLON'                            ! U:+1DLON
531
        call add2list(varname,tvar,ntrace1)
532
        varname='U:-1DLON'                            ! U:-1DLON
533
        call add2list(varname,tvar,ntrace1)
534
 
535
     ! Get the dependencies for dv(dx (DVDX)
536
     elseif ( tvar(i).eq.'DVDX' ) then
537
        varname='V:+1DLON'                            ! V:+1DLON
538
        call add2list(varname,tvar,ntrace1)
539
        varname='V:-1DLON'                            ! V:-1DLON
540
        call add2list(varname,tvar,ntrace1)
541
 
542
     ! Get the dependencies for du/dy (DUDY)
543
     elseif ( tvar(i).eq.'DUDY' ) then
544
        varname='U:+1DLAT'                            ! U:+1DLAT
545
        call add2list(varname,tvar,ntrace1)
546
        varname='U:-1DLAT'                            ! U:-1DLAT
547
        call add2list(varname,tvar,ntrace1)
548
 
549
     ! Get the dependencies for dv/dy (DVDY)
550
     elseif ( tvar(i).eq.'DVDY' ) then
551
        varname='V:+1DLAT'                            ! V:+1DLAT
552
        call add2list(varname,tvar,ntrace1)
553
        varname='V:-1DLAT'                            ! V:-1DLAT
554
        call add2list(varname,tvar,ntrace1)
555
 
556
     ! Get the dependencies for du/dp (DUDP)
557
     elseif ( tvar(i).eq.'DUDP' ) then
558
        varname='U:+1DP'                              ! U:+1DP
559
        call add2list(varname,tvar,ntrace1)
560
        varname='U:-1DP'                              ! U:-1DP
561
        call add2list(varname,tvar,ntrace1)
562
        varname='P:+1DP'                              ! P:+1DP
563
        call add2list(varname,tvar,ntrace1)
564
        varname='P:-1DP'                              ! P:-1DP
565
        call add2list(varname,tvar,ntrace1)
566
 
567
     ! Get the dependencies for dv/dp (DVDP)
568
     elseif ( tvar(i).eq.'DVDP' ) then
569
        varname='V:+1DP'                              ! V:+1DP
570
        call add2list(varname,tvar,ntrace1)
571
        varname='V:-1DP'                              ! V:-1DP
572
        call add2list(varname,tvar,ntrace1)
573
        varname='P:+1DP'                              ! P:+1DP
574
        call add2list(varname,tvar,ntrace1)
575
        varname='P:-1DP'                              ! P:-1DP
576
        call add2list(varname,tvar,ntrace1)
577
 
578
     ! Get the dependencies for dt/dx (DTDX)
579
     elseif ( tvar(i).eq.'DTDX' ) then
580
        varname='T:+1DLON'                            ! T:+1DLON
581
        call add2list(varname,tvar,ntrace1)
582
        varname='T:-1DLON'                            ! T:-1DLON
583
        call add2list(varname,tvar,ntrace1)
584
 
585
     ! Get the dependencies for dth/dy (DTHDY)
586
     elseif ( tvar(i).eq.'DTHDY' ) then
587
        varname='T:+1DLAT'                            ! T:+1DLON
588
        call add2list(varname,tvar,ntrace1)
589
        varname='T:-1DLAT'                            ! T:-1DLON
590
        call add2list(varname,tvar,ntrace1)
591
        varname='P'                                   ! P
592
        call add2list(varname,tvar,ntrace1)
593
 
594
     ! Get the dependencies for dth/dx (DTHDX)
595
     elseif ( tvar(i).eq.'DTHDX' ) then
596
        varname='T:+1DLON'                            ! T:+1DLON
597
        call add2list(varname,tvar,ntrace1)
598
        varname='T:-1DLON'                            ! T:-1DLON
599
        call add2list(varname,tvar,ntrace1)
600
        varname='P'                                   ! P
601
        call add2list(varname,tvar,ntrace1)
602
 
603
     ! Get the dependencies for dt/dy (DTDY)
604
     elseif ( tvar(i).eq.'DTDY' ) then
605
        varname='T:+1DLAT'                            ! T:+1DLON
606
        call add2list(varname,tvar,ntrace1)
607
        varname='T:-1DLAT'                            ! T:-1DLON
608
        call add2list(varname,tvar,ntrace1)
609
 
610
     ! Get the dependencies for dt/dp (DTDP)
611
     elseif ( tvar(i).eq.'DTDP' ) then
612
        varname='T:+1DP'                              ! T:+1DP
613
        call add2list(varname,tvar,ntrace1)
614
        varname='T:-1DP'                              ! T:-1DP
615
        call add2list(varname,tvar,ntrace1)
616
        varname='P:+1DP'                              ! P:+1DP
617
        call add2list(varname,tvar,ntrace1)
618
        varname='P:-1DP'                              ! P:-1DP
619
        call add2list(varname,tvar,ntrace1)
620
 
621
     ! Get the dependencies for dth/dp (DTHDP)
622
     elseif ( tvar(i).eq.'DTHDP' ) then
623
        varname='T:+1DP'                              ! T:+1DP
624
        call add2list(varname,tvar,ntrace1)
625
        varname='T:-1DP'                              ! T:-1DP
626
        call add2list(varname,tvar,ntrace1)
627
        varname='T'                                   ! T
628
        call add2list(varname,tvar,ntrace1)
629
        varname='P:+1DP'                              ! P:+1DP
630
        call add2list(varname,tvar,ntrace1)
631
        varname='P:-1DP'                              ! P:-1DP
632
        call add2list(varname,tvar,ntrace1)
633
        varname='P'                                   ! P
634
        call add2list(varname,tvar,ntrace1)
635
 
636
     ! Get the dependencies for squared Brunt Vaiäläa frequency (NSQ)
637
     elseif ( tvar(i).eq.'NSQ' ) then
638
        varname='DTHDP'                                ! DTHDP
639
        call add2list(varname,tvar,ntrace1)
640
        varname='TH'                                   ! TH
641
        call add2list(varname,tvar,ntrace1)
642
        varname='RHO'                                  ! RHO
643
        call add2list(varname,tvar,ntrace1)
644
 
645
     ! Get the dependencies for relative vorticity (RELVORT)
646
     elseif ( tvar(i).eq.'RELVORT' ) then
647
        varname='U'                                    ! U
648
        call add2list(varname,tvar,ntrace1)
649
        varname='DUDY'                                 ! DUDY
650
        call add2list(varname,tvar,ntrace1)
651
        varname='DVDX'                                 ! DVDX
652
        call add2list(varname,tvar,ntrace1)
653
 
654
     ! Get the dependencies for relative vorticity (ABSVORT)
655
     elseif ( tvar(i).eq.'ABSVORT' ) then
656
        varname='U'                                    ! U
657
        call add2list(varname,tvar,ntrace1)
658
        varname='DUDY'                                 ! DUDY
659
        call add2list(varname,tvar,ntrace1)
660
        varname='DVDX'                                 ! DVDX
661
        call add2list(varname,tvar,ntrace1)
662
 
663
     ! Get the dependencies for divergence (DIV)
664
     elseif ( tvar(i).eq.'DIV' ) then
665
        varname='V'                                    ! U
666
        call add2list(varname,tvar,ntrace1)
667
        varname='DUDX'                                 ! DUDX
668
        call add2list(varname,tvar,ntrace1)
669
        varname='DVDY'                                 ! DVDY
670
        call add2list(varname,tvar,ntrace1)
671
 
672
     ! Get the dependencies for deformation (DEF)
673
     elseif ( tvar(i).eq.'DEF' ) then
674
        call add2list(varname,tvar,ntrace1)
675
        varname='DUDX'                                 ! DUDX
676
        call add2list(varname,tvar,ntrace1)
677
        varname='DVDY'                                 ! DVDY
678
        call add2list(varname,tvar,ntrace1)
679
        varname='DUDY'                                 ! DUDY
680
        call add2list(varname,tvar,ntrace1)
681
        varname='DVDX'                                 ! DVDX
682
        call add2list(varname,tvar,ntrace1)
683
 
684
     ! Get the dependencies for potential vorticity (PV)
685
     elseif ( tvar(i).eq.'PV' ) then
686
        varname='ABSVORT'                              ! ABSVORT
687
        call add2list(varname,tvar,ntrace1)
688
        varname='DTHDP'                                ! DTHDP
689
        call add2list(varname,tvar,ntrace1)
690
        varname='DUDP'                                 ! DUDP
691
        call add2list(varname,tvar,ntrace1)
692
        varname='DVDP'                                 ! DVDP
693
        call add2list(varname,tvar,ntrace1)
694
        varname='DTHDX'                                ! DTHDX
695
        call add2list(varname,tvar,ntrace1)
696
        varname='DTHDY'                                ! DTHDY
697
        call add2list(varname,tvar,ntrace1)
698
 
699
     ! Get the dependencies for Richardson number (RI)
700
     elseif ( tvar(i).eq.'RI' ) then
701
        varname='DUDP'                                 ! DUDP
702
        call add2list(varname,tvar,ntrace1)
703
        varname='DVDP'                                 ! DVDP
704
        call add2list(varname,tvar,ntrace1)
705
        varname='NSQ'                                  ! NSQ
706
        call add2list(varname,tvar,ntrace1)
707
        varname='RHO'                                  ! RHO
708
        call add2list(varname,tvar,ntrace1)
709
 
710
     ! Get the dependencies for Ellrod&Knapp's turbulence index (TI)
711
     elseif ( tvar(i).eq.'TI' ) then
712
        varname='DEF'                                  ! DEF
713
        call add2list(varname,tvar,ntrace1)
714
        varname='DUDP'                                 ! DUDP
715
        call add2list(varname,tvar,ntrace1)
716
        varname='DVDP'                                 ! DVDP
717
        call add2list(varname,tvar,ntrace1)
718
        varname='RHO'                                  ! RHO
719
        call add2list(varname,tvar,ntrace1)
720
 
721
     endif
722
 
723
     ! Exit point for handling additional fields
724
 100   continue
725
     i = i + 1
726
 
727
  enddo
728
 
729
  ! Save the full variable name (including shift specification)
730
  do i=1,ncol
731
     varsint(i)      = varsinp(i)
732
  enddo
733
  do i=1,ntrace1
734
     varsint(i+ncol) = tvar(i)
735
  enddo
736
 
737
  ! Bojan: check that PV and TH are on trajectory
738
  if (intmode .eq. 'clustering') then
739
     pvpos=-1
740
     thpos=-1
741
     do i=1,ncol+ntrace1
742
        if (varsint(i) .eq. 'TH') then
743
        thpos=i
744
        print*,'Clustering: Found TH at position:',thpos
745
        endif
746
        if (varsint(i) .eq. 'PV') then
747
        pvpos=i
748
        print*,'Clustering: Found PV at position:',pvpos
749
        endif
750
     enddo
751
     if (thpos .eq. -1) then
752
        print*,'WARNING (clustering): Did not find TH'
753
        stop
754
     endif
755
     if (pvpos .eq. -1) then
756
        print*,'WARNING (clustering): Did not find PV'
757
        stop
758
     endif
759
  endif
760
  ! Bojan
761
 
762
  ! Split the tracing variables
763
  do i=1,ntrace0
764
    call splitvar(tvar(i),shift_val(i),shift_dir(i) )
765
  enddo
766
 
767
 
768
  ! Split the variable name and set flags
769
  do i=ntrace0+1,ntrace1
770
 
771
     ! Set the scaling factor
772
     fac(i) = 1.
773
 
774
     ! Set the base variable name, the shift and the direction
775
     call splitvar(tvar(i),shift_val(i),shift_dir(i) )
776
 
777
     ! Set the prefix of the file name for additional fields
778
     tfil(i)='*'
779
     do j=1,n_pvars
780
        if ( tvar(i).eq.pvars(j) ) tfil(i)=charp
781
     enddo
782
     do j=1,n_svars
783
        if ( tvar(i).eq.svars(j) ) tfil(i)=chars
784
     enddo
785
 
786
!    Set the computational flag
787
         if ( tvar(i).eq.'depth' ) then
788
            compfl(i) = 0
789
            tfil(i)   = charp
790
         elseif ( tfil(i).ne.'*' ) then
791
            compfl(i) = 0
792
         else
793
            compfl(i) = 1
794
         endif
795
 
796
  enddo
797
 
798
  ! Check whether the shift modes are supported
799
  do i=1,ntrace1
800
     if ( ( shift_dir(i).ne.'nil'     ).and. &
801
          ( shift_dir(i).ne.'DLON'    ).and. &
802
          ( shift_dir(i).ne.'DLAT'    ).and. &
803
          ( shift_dir(i).ne.'DP'      ).and. &
804
          ( shift_dir(i).ne.'HPA'     ).and. &
805
          ( shift_dir(i).ne.'KM(LON)' ).and. &
806
          ( shift_dir(i).ne.'KM(LAT)' ).and. &
807
          ( shift_dir(i).ne.'H'       ).and. &
808
          ( shift_dir(i).ne.'MIN'     ).and. &
809
          ( shift_dir(i).ne.'INDP'    ) ) then
810
        print*,' ERROR: shift mode ',trim(shift_dir(i)), ' not supported'
811
        stop
812
     endif
813
  enddo
814
 
815
  ! Write status information
816
  print*
817
  print*,'---- COMPLETE TABLE FOR TRACING -------------------------'
818
  print*
819
  do i=1,ntrace1
820
     if ( ( shift_dir(i).ne.'nil' ) ) then
821
        write(*,'(i4,a4,a8,f10.2,a8,3x,a1,i5)') i,' : ',trim(tvar(i)), &
822
             shift_val(i),trim(shift_dir(i)),tfil(i),compfl(i)
823
     else
824
        write(*,'(i4,a4,a8,10x,8x,3x,a1,i5)') &
825
             i,' : ',trim(tvar(i)),tfil(i),compfl(i)
826
     endif
827
  enddo
828
 
829
  ! --------------------------------------------------------------------
830
  ! Prepare the internal and output trajectories
831
  ! --------------------------------------------------------------------
832
 
833
  ! Allocate memory for internal trajectories
834
  allocate(traint(ntra,ntim,ncol+ntrace1),stat=stat)
835
  if (stat.ne.0) print*,'*** error allocating array traint   ***'
836
 
837
  ! Copy input to output trajectory
838
  do i=1,ntra
839
     do j=1,ntim
840
        do k=1,ncol
841
           traint(i,j,k)=trainp(i,j,k)
842
        enddo
843
     enddo
844
  enddo
845
 
846
  ! Set the flags for ready fields/colums - at begin only read-in fields are ready
847
  do i=1,ncol
848
     fok(i) = 1
849
  enddo
850
  do i=ncol+1,ntrace1
851
     fok(i) = 0
852
  enddo
853
 
854
  ! --------------------------------------------------------------------
855
  ! Trace the fields (fields available on input files)
856
  ! --------------------------------------------------------------------
857
 
858
  print*
859
  print*,'---- TRACING FROM PRIMARY AND SECONDARY DATA FILES ------'
860
 
861
  ! Loop over all tracing fields
862
  do i=1,ntrace1
863
 
864
      ! Skip fields which must be computed (compfl=1), will be handled later
865
      if (compfl(i).ne.0)  goto 110
866
 
867
      ! Write some status information
868
      print*
869
      print*,' Now tracing             : ', trim(tvar(i)),shift_val(i),trim(shift_dir(i)),compfl(i),' ',trim(tfil(i))
870
 
871
      ! Set the flag for ready field/column
872
      fok(ncol+i) = 1
873
 
874
      ! Reset flags for load manager
875
      iloaded0 = -1
876
      iloaded1 = -1
877
 
878
      ! Reset the counter for fields outside domain
879
      noutside = 0
880
      err_c1   = 0
881
      err_c2   = 0
882
      err_c3   = 0
883
 
884
      ! Loop over all times
885
      do j=1,ntim
886
 
887
         ! Convert trajectory time from hh.mm to fractional time
888
         call hhmm2frac(trainp(1,j,1),tfrac)
889
 
890
         ! Shift time if requested
891
         if ( shift_dir(i).eq.'H' ) then
892
            tfrac = tfrac + shift_val(i)
893
         elseif ( shift_dir(i).eq.'MIN' ) then
894
            tfrac = tfrac + shift_val(i)/60.
895
         endif
896
 
897
         ! Get the times which are needed
898
         itime0   = int(abs(tfrac-tstart)/timeinc) + 1
899
         time0    = tstart + fbflag * real(itime0-1) * timeinc
900
         itime1   = itime0 + 1
901
         time1    = time0 + fbflag * timeinc
902
         if ( itime1.gt.numdat ) then
903
            itime1 = itime0
904
            time1  = time0
905
         endif
906
 
907
         ! Load manager: Check whether itime0 can be copied from itime1
908
         if ( itime0.eq.iloaded1 ) then
909
            f3t0     = f3t1
910
            p3t0     = p3t1
911
            spt0     = spt1
912
            iloaded0 = itime0
913
         endif
914
 
915
         ! Load manager: Check whether itime1 can be copied from itime0
916
         if ( itime1.eq.iloaded0 ) then
917
            f3t1     = f3t0
918
            p3t1     = p3t0
919
            spt1     = spt0
920
            iloaded1 = itime1
921
         endif
922
 
923
         ! Load manager:  Load first time (tracing variable and grid)
924
         if ( itime0.ne.iloaded0 ) then
925
 
926
            filename = tfil(i)//dat(itime0)
927
            call frac2hhmm(time0,tload)
928
            varname  = tvar(i)
929
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
930
            call input_open (fid,filename)
931
            call input_wind &
932
                 (fid,varname,f3t0,tload,stagz,mdv, &
933
                 xmin,xmax,ymin,ymax,dx,dy,nx,ny,nz,timecheck)
934
            call input_close(fid)
935
 
936
          ! Load grid from primary P files -> needed in ORA because lev not on S file
937
            filename = charp//dat(itime0)
938
            call input_open (fid,filename)
939
            call input_grid &
940
                 (fid,'lev',xmin,xmax,ymin,ymax,dx,dy,nx,ny, &
941
                 tload,pollon,pollat,p3t0,spt0,nz,stagz, &
942
                 timecheck)
943
            call input_close(fid)
944
 
945
            iloaded0 = itime0
946
 
947
         endif
948
 
949
         ! Load manager: Load second time (tracing variable and grid)
950
         if ( itime1.ne.iloaded1 ) then
951
 
952
            filename = tfil(i)//dat(itime1)
953
            call frac2hhmm(time1,tload)
954
            varname  = tvar(i)
955
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
956
            call input_open (fid,filename)
957
            call input_wind &
958
                 (fid,varname,f3t1,tload,stagz,mdv, &
959
                 xmin,xmax,ymin,ymax,dx,dy,nx,ny,nz,timecheck)
960
          !  call input_grid &
961
          !       (fid,'lev',xmin,xmax,ymin,ymax,dx,dy,nx,ny, &
962
          !       tload,pollon,pollat,p3t1,spt1,nz,stagz, &
963
          !       timecheck)
964
            call input_close(fid)
965
 
966
          ! Load grid from primary P files -> needed in ORA because lev not on S file
967
            filename = charp//dat(itime1)
968
            call input_open (fid,filename)
969
            call input_grid &
970
                 (fid,'lev',xmin,xmax,ymin,ymax,dx,dy,nx,ny, &
971
                 tload,pollon,pollat,p3t1,spt1,nz,stagz, &
972
                 timecheck)
973
            call input_close(fid)
974
            iloaded1 = itime1
975
 
976
         endif
977
 
978
         ! Loop over all trajectories
979
         do k=1,ntra
980
 
981
            ! Set the horizontal position where to interpolate to
982
            x0       = traint(k,j,2)                          ! Longitude
983
            y0       = traint(k,j,3)                          ! Latitude
984
 
985
            ! Set the vertical position where to interpolate to
986
            if ( nz.gt.1 ) then
987
               p0 = traint(k,j,4)                             ! Pressure (3D tracing)
988
            else
989
               p0 = 0.                                     ! Lowest level (2D tracing)
990
            endif
991
 
992
            ! Set negative pressures to mdv
993
            if (p0.lt.0.) then
994
	        f0 = mdv
995
                goto 109
996
            endif
997
 
998
            ! Set the relative time
999
            call hhmm2frac(traint(k,j,1),tfrac)
1000
            reltpos0 = fbflag * (tfrac-time0)/timeinc
1001
 
1002
            ! Make adjustments depending on the shift flag
1003
            if ( shift_dir(i).eq.'DLON' ) then                         ! DLON
1004
               x0 = x0 + shift_val(i)
1005
 
1006
            elseif  ( shift_dir(i).eq.'DLAT' ) then                    ! DLAT
1007
               y0 = y0 + shift_val(i)
1008
 
1009
            elseif ( shift_dir(i).eq.'KM(LON)' ) then                  ! KM(LON)
1010
               x0 = x0 + shift_val(i)/deg2km * 1./cos(y0*pi180)
1011
 
1012
            elseif ( shift_dir(i).eq.'KM(LAT)' ) then                  ! KM(LAT)
1013
               y0 = y0 + shift_val(i)/deg2km
1014
 
1015
            elseif ( shift_dir(i).eq.'HPA' ) then                      ! HPA
1016
               p0 = p0 + shift_val(i)
1017
 
1018
            elseif ( shift_dir(i).eq.'DP' ) then                       ! DP
1019
               call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0, &
1020
                    p3t0,p3t1,spt0,spt1,3,nx,ny,nz,xmin,ymin,dx,dy,mdv)
1021
               pind = pind - shift_val(i)
1022
               p0   = int_index4(p3t0,p3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
1023
 
1024
            elseif ( shift_dir(i).eq.'INDP' ) then
1025
               p0   = int_index4(p3t0,p3t1,nx,ny,nz,xind,yind,shift_val(i),reltpos0,mdv)
1026
 
1027
            endif
1028
 
1029
            ! Handle periodic boundaries in zonal direction
1030
            if ( (x0.gt.xmax).and.(per.ne.0) ) x0 = x0 - 360.
1031
            if ( (x0.lt.xmin).and.(per.ne.0) ) x0 = x0 + 360.
1032
 
1033
            ! Handle pole problems for hemispheric data (taken from caltra.f)
1034
            if ((hem.eq.1).and.(y0.gt.90.)) then
1035
               print*,'WARNING: y0>90 ',y0,' => setting to 180-y0 ',180.-y0
1036
               y0=180.-y0
1037
               x0=x0+per/2.
1038
            endif
1039
            if ((hem.eq.1).and.(y0.lt.-90.)) then
1040
               print*,'WARNING: y0<-90 ',y0,' => setting to -180-y0 ',-180.-y0
1041
               y0=-180.-y0
1042
               x0=x0+per/2.
1043
            endif
1044
            ! Get the index where to interpolate (x0,y0,p0)
1045
            if ( (abs(x0-mdv).gt.eps).and. (abs(y0-mdv).gt.eps) ) then
1046
               call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0, &
1047
                    p3t0,p3t1,spt0,spt1,3,nx,ny,nz,xmin,ymin,dx,dy,mdv)
1048
            else
1049
               xind = mdv
1050
               yind = mdv
1051
               pind = mdv
1052
            endif
1053
 
1054
           ! Check if point is within grid (keep indices if ok)
1055
            if ( (xind.ge.1.).and.(xind.le.real(nx)).and. &
1056
                 (yind.ge.1.).and.(yind.le.real(ny)).and. &
1057
                 (pind.ge.1.).and.(pind.le.real(nz)) ) then
1058
		     xind = xind
1059
		     yind = yind
1060
		     pind = pind
1061
 
1062
            ! Check if pressure is outside, but rest okay => adjust to lowest or highest level
1063
            elseif ( (xind.ge.1.).and.(xind.le.real(nx)).and. (yind.ge.1.).and.(yind.le.real(ny)) ) then ! only vertical problem
1064
 
1065
               if ( pind.gt.nz ) then ! pressure too low, index too high
1066
                 err_c1 = err_c1 + 1
1067
                 if ( err_c1.lt.10 ) then
1068
                    write(*,'(Af5.3A)') ' WARNING: pressure too low (pind = ',pind,') => adjusted to highest level (pind=nz.)'
1069
                    print*,'(x0,y0,p0)=',x0,y0,p0
1070
                    pind = real(nz)
1071
                 elseif ( err_c1.eq.10 ) then
1072
                    print*,' WARNING: more pressures too low -> adjusted to highest level '
1073
                    pind = real(nz)
1074
                 else
1075
                    pind = real(nz)
1076
                 endif
1077
 
1078
               elseif (pind.lt.1.) then ! pressure too high, index too low
1079
                 err_c2 = err_c2 + 1
1080
                 if ( err_c2.lt.10 ) then
1081
                    write(*,'(Af5.3A)') ' WARNING: pressure too high (pind = ',pind,') => adjusted to lowest level, (pind=1.)'
1082
                    print*,'(x0,y0,p0)=',x0,y0,p0
1083
                    pind = 1.
1084
                 elseif ( err_c2.eq.10 ) then
1085
                    print*,' WARNING: more pressures too high -> adjusted to lowest level '
1086
                    pind = 1.
1087
                 else
1088
                    pind = 1.
1089
                 endif
1090
 
1091
              endif
1092
 
1093
            ! Grid point is outside!
1094
            else
1095
 
1096
               err_c3 = err_c3 + 1
1097
               if ( err_c3.lt.10 ) then
1098
                  print*,'ERROR: point is outside grid (horizontally)'
1099
                  print*,'   Trajectory # ',k
1100
                  print*,'   Position     ',x0,y0,p0
1101
                  print*,'  (xind,yind):  ',xind,yind
1102
                  xind          = mdv
1103
                  yind          = mdv
1104
                  pind          = mdv
1105
                  traint(k,j,2) = mdv  
1106
                  traint(k,j,3) = mdv  
1107
                  traint(k,j,4) = mdv  
1108
               elseif ( err_c3.eq.10 ) then
1109
                  print*,'ERROR: more points outside grid (horizontally)'
1110
                  xind          = mdv
1111
                  yind          = mdv
1112
                  pind          = mdv
1113
                  traint(k,j,2) = mdv  
1114
                  traint(k,j,3) = mdv  
1115
                  traint(k,j,4) = mdv  
1116
               else
1117
                  xind          = mdv
1118
                  yind          = mdv
1119
                  pind          = mdv
1120
                  traint(k,j,2) = mdv  
1121
                  traint(k,j,3) = mdv  
1122
                  traint(k,j,4) = mdv  
1123
               endif
1124
 
1125
            endif
1126
 
1127
            ! ------------------------ NEAREST mode ------------------------------- 
1128
            ! Interpolate to nearest grid point
1129
            if ( intmode.eq.'nearest') then
1130
 
1131
               xind = real( nint(xind) )
1132
               yind = real( nint(yind) )
1133
               pind = real( nint(pind) )
1134
 
1135
               if ( xind.lt.1.  ) xind = 1.
1136
               if ( xind.gt.nx  ) xind = real(nx)
1137
               if ( yind.lt.1.  ) yind = 1.
1138
               if ( yind.gt.ny  ) yind = real(ny)
1139
 
1140
               if ( pind.lt.1.  ) pind = 1.
1141
               if ( pind.gt.nz  ) pind = real(nz)
1142
 
1143
               if ( abs(reltpos0).ge.eps ) then
1144
                  print*,'ERROR (nearest): reltpos != 0',reltpos0
1145
                  stop
1146
               endif
1147
 
1148
               ! interpolate
1149
               f0 = int_index4(f3t0,f3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
1150
 
1151
            ! ------------------------ end NEAREST mode ------------------------------- 
1152
 
1153
            ! ------------------------ CLUSTERING mode ------------------------------- Bojan
1154
            elseif (intmode.eq.'clustering') then
1155
               if (varname.ne.'LABEL' ) then
1156
                  print*,'ERROR (clustering): varname is not LABEL'
1157
                  stop
1158
               endif
1159
 
1160
            ! Get indices of box around the point
1161
            xindb=floor(xind)
1162
            xindf=ceiling(xind)
1163
            yindb=floor(yind)
1164
            yindf=ceiling(yind)
1165
            pindb=floor(pind)
1166
            pindf=ceiling(pind)
1167
 
1168
            ! Make sure all points are within grid
1169
            if ( xindb.lt.1 ) xindb = 1
1170
            if ( xindf.lt.1 ) xindf = 1
1171
            if ( xindb.gt.nx ) xindb = nx
1172
            if ( xindf.gt.nx ) xindf = nx
1173
            if ( yindb.lt.1 ) yindb = 1
1174
            if ( yindf.lt.1 ) yindf = 1
1175
            if ( yindb.gt.ny ) yindb = ny
1176
            if ( yindf.gt.ny ) yindf = ny
1177
            if ( pindb.lt.1 ) pindb = 1
1178
            if ( pindf.lt.1 ) pindf = 1
1179
            if ( pindb.gt.nz ) pindb = nz
1180
            if ( pindf.gt.nz ) pindf = nz
1181
 
1182
            ! Shift one point if they are equal
1183
            if ( xindb.eq.xindf ) then
1184
               if ( xindf.eq.nx ) then
1185
                  xindb=nx-1
1186
               else
1187
                  xindf=xindb+1
1188
               endif
1189
            endif
1190
            if ( yindb.eq.yindf ) then
1191
               if ( yindf.eq.ny ) then
1192
                  yindb=ny-1
1193
               else
1194
                  yindf=yindb+1
1195
               endif
1196
            endif
1197
            if ( pindb.eq.pindf ) then
1198
               if ( pindf.eq.nz ) then
1199
                  pindb=nz-1
1200
               else
1201
                  pindf=pindb+1
1202
               endif
1203
            endif
1204
            ! Give warnings and stop if problems occur
1205
            if ( xindb.eq.xindf ) then
1206
               print*,'ERROR (clustering): xindb=xindf'
1207
               print*,xind,xindb,xindf
1208
               stop
1209
            endif
1210
            if ( yindb.eq.yindf ) then
1211
               print*,'ERROR (clustering): yindb=yindf'
1212
               print*,yind,yindb,yindf
1213
               stop
1214
            endif
1215
            if ( pindb.eq.pindf ) then
1216
               print*,'ERROR (clustering): pindb=pindf'
1217
               print*,pind,pindb,pindf
1218
               stop
1219
            endif
1220
            if ( ( xindb.lt.1 ).or.( xindf.gt.nx ) ) then
1221
               print*,'ERROR (clustering): xindb/f outside'
1222
               print*,xind,xindb,xindf
1223
               stop
1224
            endif
1225
            if ( ( yindb.lt.1 ).or.( yindf.gt.ny ) ) then
1226
               print*,'ERROR (clustering): yindb/f outside'
1227
               print*,yind,yindb,yindf
1228
               stop
1229
            endif
1230
            if ( ( pindb.lt.1 ).or.( pindf.gt.nz ) ) then
1231
               print*,'ERROR (clustering): pindb/f outside'
1232
               print*,pind,pindb,pindf
1233
               stop
1234
            endif
1235
            if ( abs(reltpos0).ge.eps ) then
1236
               print*,'ERROR (clustering): reltpos != 0',reltpos0
1237
               stop
1238
            endif
1239
 
1240
            ! Get Value in Box
1241
            lblcount=(/0,0,0,0,0/)
1242
 
1243
            lbl(1) = f3t0( xindb + nx*(yindb-1) + nx*ny*(pindb-1) )
1244
            lbl(2) = f3t0( xindf + nx*(yindb-1) + nx*ny*(pindb-1) )
1245
            lbl(3) = f3t0( xindb + nx*(yindf-1) + nx*ny*(pindb-1) )
1246
            lbl(4) = f3t0( xindf + nx*(yindf-1) + nx*ny*(pindb-1) )
1247
            lbl(5) = f3t0( xindb + nx*(yindb-1) + nx*ny*(pindf-1) )
1248
            lbl(6) = f3t0( xindf + nx*(yindb-1) + nx*ny*(pindf-1) )
1249
            lbl(7) = f3t0( xindb + nx*(yindf-1) + nx*ny*(pindf-1) )
1250
            lbl(8) = f3t0( xindf + nx*(yindf-1) + nx*ny*(pindf-1) )
1251
 
1252
            ! Count the number of times every label appears
1253
            do lci=1,5
1254
               do lcj=1,8
1255
                  if ( abs(lbl(lcj)-lci).lt.eps ) then
1256
                     lblcount(lci)=lblcount(lci)+1
1257
                  endif
1258
               enddo
1259
            enddo
1260
 
1261
            ! Set to -9 to detect if no label was assigned in the end
1262
            f0=-9
1263
 
1264
            ! Stratosphere (PV)
1265
            if ( abs(traint(k,j,pvpos)) .ge. tropo_pv ) then
1266
               if ( (lblcount(2).ge.lblcount(3)).and. (lblcount(2).ge.lblcount(5)) ) then
1267
                  f0=2
1268
               elseif ( lblcount(3).ge.lblcount(5) ) then
1269
                  f0=3
1270
               elseif ( lblcount(5).gt.lblcount(3) ) then
1271
                  f0=5
1272
               endif
1273
            endif
1274
 
1275
            ! Troposphere (PV)
1276
            if ( abs(traint(k,j,pvpos)) .lt. tropo_pv ) then
1277
               if ( lblcount(1).ge.lblcount(4) ) then
1278
               f0=1
1279
               elseif ( lblcount(4).gt.lblcount(1) ) then
1280
               f0=4
1281
               endif
1282
            endif
1283
 
1284
            ! Stratosphere (TH)
1285
            if ( traint(k,j,thpos) .ge. tropo_th ) then
1286
               f0=2
1287
            endif
1288
 
1289
            if (f0.eq.-9) then
1290
               print*,'ERROR (Clustering): No label assigned!'
1291
               stop
1292
            endif
1293
            ! ------------------------ end CLUSTERING mode -------------------------------
1294
 
1295
            ! ------------------------ CIRCLE modes ------------------------------- Bojan
1296
            ! elseif (not clustering but one of the possible circle modes)
1297
            elseif ( (intmode.eq.'circle_avg') .or. (intmode.eq.'circle_min') .or. (intmode.eq.'circle_max') ) then
1298
 
1299
            ! reset arrays for this point
1300
            connect=0
1301
            stackx=0
1302
            stacky=0
1303
            circlelon=0
1304
            circlelat=0
1305
            circlef=0
1306
            circlearea=0
1307
 
1308
            ! Get indices of one coarse grid point within search radius (nint=round to next integer)
1309
            if ( sdis(x0,y0,longrid(nint(xind)),latgrid(nint(yind))) .gt. radius) then
1310
               print*,'ERROR (circle): Search radius is too small... (1). r =',radius
1311
               print*,'Distance to nint grid point (minimum search radius)=',sdis(x0,y0,longrid(nint(xind)),latgrid(nint(yind)))
1312
               stop
1313
            endif
1314
 
1315
            ! Initialize stack with nint(xind),nint(yind)
1316
            kst=0 ! counts the number of points in circle
1317
            stackx(1)=nint(xind)
1318
            stacky(1)=nint(yind)
1319
            sp=1 ! stack counter
1320
            do while (sp.ne.0)
1321
 
1322
            ! Get an element from stack
1323
             ist=stackx(sp)
1324
             jst=stacky(sp)
1325
             sp=sp-1
1326
 
1327
            ! Get distance from reference point
1328
             dist=sdis(x0,y0,longrid(ist),latgrid(jst))
1329
 
1330
            ! Check whether distance is smaller than search radius: connected
1331
             if (dist.lt.radius) then
1332
 
1333
            ! Increase total stack index
1334
              kst=kst+1
1335
              circlelon(kst)=longrid(ist)
1336
              circlelat(kst)=latgrid(jst)
1337
 
1338
            ! Interpolate field to position of point (interpolation in time!) 
1339
              circlef(kst) = int_index4(f3t0,f3t1,nx,ny,nz,real(ist),real(jst),pind,reltpos0,mdv)
1340
 
1341
            ! Calculate area of point (for circle_avg mode only)
1342
              if ( intmode .eq. 'circle_avg' ) then
1343
                 circlearea(kst) = pir/(nx-1)*(sin(pi180*abs(circlelat(kst)))-sin(pi180*(abs(circlelat(kst))-dy)))
1344
              endif
1345
 
1346
            ! Mark this point as visited
1347
              connect(ist,jst)=1
1348
 
1349
            ! Get coordinates of neighbouring points and implement periodicity
1350
              mr=ist+1
1351
              if (mr.gt.nx) mr=1
1352
              ml=ist-1
1353
              if (ml.lt.1) ml=nx
1354
              nu=jst+1
1355
              if (nu.gt.ny) nu=ny
1356
              nd=jst-1
1357
              if (nd.lt.1) nd=1
1358
 
1359
            ! Update stack with neighbouring points
1360
              if (connect(mr,jst).ne. 1) then
1361
                 connect(mr,jst)=1
1362
                 sp=sp+1
1363
                 stackx(sp)=mr
1364
                 stacky(sp)=jst
1365
              endif
1366
              if (connect(ml,jst).ne. 1) then
1367
                 connect(ml,jst)=1
1368
                 sp=sp+1
1369
                 stackx(sp)=ml
1370
                 stacky(sp)=jst
1371
              endif
1372
              if (connect(ist,nd).ne. 1) then
1373
                 connect(ist,nd)=1
1374
                 sp=sp+1
1375
                 stackx(sp)=ist
1376
                 stacky(sp)=nd
1377
              endif
1378
              if (connect(ist,nu).ne. 1) then
1379
                 connect(ist,nu)=1
1380
                 sp=sp+1
1381
                 stackx(sp)=ist
1382
                 stacky(sp)=nu
1383
              endif
1384
 
1385
             endif ! endif radius is smaller => end of updating stack
1386
 
1387
            end do ! end working on stack 
1388
 
1389
            if (kst.ge.1) then
1390
               ! Choose output depending on intmode
1391
               if ( intmode .eq. 'circle_avg' ) then
1392
                  ! calculate area-weighted average of f in circle
1393
                  circlesum=0.
1394
                  do l=1,kst
1395
                     circlesum=circlesum+circlef(l)*circlearea(l)
1396
                  enddo
1397
                  circleavg=circlesum/sum(circlearea(1:kst))
1398
                  !print*,'area-weighted average of f in circle=',circleavg
1399
                  f0=circleavg
1400
               elseif ( intmode .eq. 'circle_min' ) then
1401
                  ! calculate minimum in circle
1402
                  circlemin=circlef(1)
1403
                  do l=1,kst
1404
                     if (circlef(l) .lt. circlemin) then
1405
                        circlemin=circlef(l)
1406
                     endif
1407
                  enddo
1408
                  !print*,'minimum of f in circle=',circlemin       
1409
                  f0=circlemin
1410
               elseif ( intmode .eq. 'circle_max' ) then             
1411
                  ! calculate maximum in circle
1412
                  circlemax=circlef(1)
1413
                  do l=1,kst
1414
                     if (circlef(l) .gt. circlemax) then
1415
                        circlemax=circlef(l)
1416
                     endif
1417
                  enddo
1418
                  !print*,'maximum of f in circle=',circlemax
1419
                  f0=circlemax
1420
               else 
1421
                  print*,'ERROR (circle): intmode not valid!'
1422
                  stop
1423
               endif
1424
            else
1425
               print*,'ERROR (circle): Search radius is too small... (2). r =',radius
1426
               stop
1427
            endif
1428
 
1429
            ! ------------------------ end CIRCLE modes -------------------------------
1430
 
1431
            ! ------------------------ NORMAL mode -------------------------------
1432
            else ! not clustering nor circle: NORMAL mode
1433
 
1434
            ! Check if point is within grid
1435
!            if ( (xind.ge.1.).and.(xind.le.real(nx)).and. &
1436
!                 (yind.ge.1.).and.(yind.le.real(ny)).and. &
1437
!                 (pind.ge.1.).and.(pind.le.real(nz)) ) then
1438
!
1439
            ! Do the interpolation: everthing is ok
1440
               f0 = int_index4(f3t0,f3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
1441
 
1442
!            ! Check if pressure is outside, but rest okay: adjust to lowest or highest level
1443
!            elseif ( (xind.ge.1.).and.(xind.le.real(nx)).and. (yind.ge.1.).and.(yind.le.real(ny)) ) then ! only vertical problem
1444
!               if ( pind.gt.nz ) then ! pressure too low, index too high
1445
!                 pind = real(nz)
1446
!                 print*,' Warning: pressure too low -> adjusted to highest level, pind=nz.'
1447
!                 print*,'(x0,y0,p0)=',x0,y0,p0
1448
!               elseif (pind.lt.1.) then ! pressure too high, index too low
1449
!                 pind = 1.
1450
!                 print*,' Warning: pressure too high -> adjusted to lowest level, pind=1.'
1451
!                 print*,'(x0,y0,p0)=',x0,y0,p0
1452
!              endif
1453
!              f0 = int_index4(f3t0,f3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
1454
 
1455
!            ! Less than 10 outside
1456
!            elseif (noutside.lt.10) then
1457
!               print*,' ',trim(tvar(i)),' @ ',x0,y0,p0,'outside'
1458
!               f0       = mdv
1459
!               noutside = noutside + 1
1460
!
1461
!            ! More than 10 outside
1462
!            elseif (noutside.eq.10) then
1463
!               print*,' ...more than 10 outside...'
1464
!               f0       = mdv
1465
!               noutside = noutside + 1
1466
 
1467
!            ! Else (not everything okay and also not 'tolerated cases') set to missing data
1468
!            else
1469
!               f0       = mdv
1470
!            endif
1471
 
1472
            ! ------------------------ end NORMAL mode -------------------------------
1473
            endif ! end if nearest case
1474
 
1475
           ! Exit for loop over all trajectories and times -save interpolated value
1476
 109        continue
1477
 
1478
            ! Save the new field
1479
            if ( abs(f0-mdv).gt.eps) then
1480
               traint(k,j,ncol+i) = f0
1481
            else
1482
               traint(k,j,ncol+i) = mdv
1483
            endif
1484
 
1485
         enddo ! end loop over all trajectories
1486
 
1487
      enddo ! end loop over all times
1488
 
1489
      ! Exit point for loop over all tracing variables
1490
 110   continue
1491
 
1492
   enddo ! end loop over all variables
1493
 
1494
  ! --------------------------------------------------------------------
1495
  ! Calculate additional fields along the trajectories
1496
  ! --------------------------------------------------------------------
1497
 
1498
  print*
1499
  print*,'---- CALCULATE ADDITIONAL FIELDS FROM TRAJECTORY TABLE --'
1500
 
1501
  ! Loop over all tracing fields
1502
  do i=ntrace1,1,-1
1503
 
1504
      ! Skip fields which must not be computed (compfl=0)
1505
      if (compfl(i).eq.0) goto 120
1506
 
1507
      ! Write some status information
1508
      print*
1509
      write(*,'(a10,f10.2,a5,i3,3x,a2)') &
1510
           trim(tvar(i)),shift_val(i),trim(shift_dir(i)),compfl(i),trim(tfil(i))
1511
 
1512
      ! Loop over trajectories and times
1513
      do j=1,ntra
1514
      do k=1,ntim
1515
 
1516
         ! Potential temperature (TH)
1517
         if  ( varsint(i+ncol).eq.'TH' ) then
1518
 
1519
            varname='T'
1520
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1521
            varname='p'
1522
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1523
 
1524
            call calc_TH  (traint(j,k,ncol+i), traint(j,k,ind1), &
1525
                 traint(j,k,ind2) )
1526
 
1527
         ! Density (RHO)
1528
         elseif  ( varsint(i+ncol).eq.'RHO' ) then
1529
 
1530
            varname='T'
1531
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1532
            varname='p'
1533
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1534
 
1535
            call calc_RHO (traint(j,k,ncol+i), traint(j,k,ind1), &
1536
                 traint(j,k,ind2) )
1537
 
1538
         ! Relative humidity (RH)
1539
         elseif  ( varsint(i+ncol).eq.'RH' ) then
1540
 
1541
            varname='T'
1542
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1543
            varname='p'
1544
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1545
            varname='Q'
1546
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1547
 
1548
            call calc_RH (traint(j,k,ncol+i), traint(j,k,ind1), &
1549
                 traint(j,k,ind2),traint(j,k,ind3) )
1550
 
1551
         ! Equivalent potential temperature (THE)
1552
         elseif  ( varsint(i+ncol).eq.'THE' ) then
1553
 
1554
            varname='T'
1555
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1556
            varname='p'
1557
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1558
            varname='Q'
1559
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1560
 
1561
            call calc_THE (traint(j,k,ncol+i), traint(j,k,ind1), &
1562
                 traint(j,k,ind2),traint(j,k,ind3) )
1563
 
1564
         ! Latent heating rate (LHR)
1565
         elseif  ( varsint(i+ncol).eq.'LHR' ) then
1566
 
1567
            varname='T'
1568
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1569
            varname='p'
1570
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1571
            varname='Q'
1572
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1573
            varname='OMEGA'
1574
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1575
            varname='RH'
1576
            call list2ind (ind5,varname,varsint,fok,ncol+ntrace1)
1577
 
1578
            call calc_LHR (traint(j,k,ncol+i), traint(j,k,ind1), &
1579
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4),traint(j,k,ind5) )
1580
 
1581
         ! Wind speed (VEL)
1582
         elseif  ( varsint(i+ncol).eq.'VEL' ) then
1583
 
1584
            varname='U'
1585
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1586
            varname='V'
1587
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1588
 
1589
            call calc_VEL (traint(j,k,ncol+i), traint(j,k,ind1), &
1590
                 traint(j,k,ind2) )
1591
 
1592
         ! Wind direction (DIR)
1593
         elseif  ( varsint(i+ncol).eq.'DIR' ) then
1594
 
1595
            varname='U'
1596
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1597
            varname='V'
1598
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1599
 
1600
            call calc_DIR (traint(j,k,ncol+i), traint(j,k,ind1), &
1601
                 traint(j,k,ind2) )
1602
 
1603
         ! Zonal gradient of U (DUDX)
1604
         elseif  ( varsint(i+ncol).eq.'DUDX' ) then
1605
 
1606
            varname='U:+1DLON'
1607
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1608
            varname='U:-1DLON'
1609
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1610
            varname='lat'
1611
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1612
 
1613
            call calc_DUDX (traint(j,k,ncol+i), traint(j,k,ind1), &
1614
                 traint(j,k,ind2),traint(j,k,ind3) )
1615
 
1616
         ! Zonal gradient of V (DVDX)
1617
         elseif  ( varsint(i+ncol).eq.'DVDX' ) then
1618
 
1619
            varname='V:+1DLON'
1620
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1621
            varname='V:-1DLON'
1622
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1623
            varname='lat'
1624
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1625
 
1626
            call calc_DVDX (traint(j,k,ncol+i), traint(j,k,ind1), &
1627
                 traint(j,k,ind2),traint(j,k,ind3) )
1628
 
1629
         ! Zonal gradient of T (DTDX)
1630
         elseif  ( varsint(i+ncol).eq.'DVDX' ) then
1631
 
1632
            varname='T:+1DLON'
1633
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1634
            varname='T:-1DLON'
1635
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1636
            varname='lat'
1637
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1638
 
1639
            call calc_DTDX (traint(j,k,ncol+i), traint(j,k,ind1), &
1640
                 traint(j,k,ind2),traint(j,k,ind3) )
1641
 
1642
         ! Zonal gradient of TH (DTHDX)
1643
         elseif  ( varsint(i+ncol).eq.'DTHDX' ) then
1644
 
1645
            varname='T:+1DLON'
1646
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1647
            varname='T:-1DLON'
1648
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1649
            varname='P'
1650
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1651
            varname='lat'
1652
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1653
 
1654
            call calc_DTHDX (traint(j,k,ncol+i), traint(j,k,ind1), &
1655
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1656
 
1657
         ! Meridional gradient of U (DUDY)
1658
         elseif  ( varsint(i+ncol).eq.'DUDY' ) then
1659
 
1660
            varname='U:+1DLAT'
1661
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1662
            varname='U:-1DLAT'
1663
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1664
 
1665
            call calc_DUDY (traint(j,k,ncol+i), traint(j,k,ind1), &
1666
                 traint(j,k,ind2) )
1667
 
1668
         ! Meridional gradient of V (DVDY)
1669
         elseif  ( varsint(i+ncol).eq.'DVDY' ) then
1670
 
1671
            varname='V:+1DLAT'
1672
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1673
            varname='V:-1DLAT'
1674
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1675
 
1676
            call calc_DVDY (traint(j,k,ncol+i), traint(j,k,ind1), &
1677
                 traint(j,k,ind2) )
1678
 
1679
         ! Meridional gradient of T (DTDY)
1680
         elseif  ( varsint(i+ncol).eq.'DTDY' ) then
1681
 
1682
            varname='T:+1DLAT'
1683
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1684
            varname='T:-1DLAT'
1685
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1686
 
1687
            call calc_DTDY (traint(j,k,ncol+i), traint(j,k,ind1), &
1688
                 traint(j,k,ind2) )
1689
 
1690
         ! Meridional gradient of TH (DTHDY)
1691
         elseif  ( varsint(i+ncol).eq.'DTHDY' ) then
1692
 
1693
            varname='T:+1DLAT'
1694
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1695
            varname='T:-1DLAT'
1696
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1697
            varname='P'
1698
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1699
 
1700
            call calc_DTDY (traint(j,k,ncol+i), traint(j,k,ind1), &
1701
                 traint(j,k,ind2),traint(j,k,ind3) )
1702
 
1703
 
1704
         ! Vertical wind shear DU/DP (DUDP)
1705
         elseif  ( varsint(i+ncol).eq.'DUDP' ) then
1706
 
1707
            varname='U:+1DP'
1708
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1709
            varname='U:-1DP'
1710
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1711
            varname='P:+1DP'
1712
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1713
            varname='P:-1DP'
1714
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1715
 
1716
            call calc_DUDP (traint(j,k,ncol+i), traint(j,k,ind1), &
1717
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1718
 
1719
         ! Vertical wind shear DV/DP (DVDP)
1720
         elseif  ( varsint(i+ncol).eq.'DVDP' ) then
1721
 
1722
            varname='V:+1DP'
1723
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1724
            varname='V:-1DP'
1725
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1726
            varname='P:+1DP'
1727
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1728
            varname='P:-1DP'
1729
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1730
 
1731
            call calc_DVDP (traint(j,k,ncol+i), traint(j,k,ind1), &
1732
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1733
 
1734
         ! Vertical derivative of T (DTDP)
1735
         elseif  ( varsint(i+ncol).eq.'DTDP' ) then
1736
 
1737
            varname='T:+1DP'
1738
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1739
            varname='T:-1DP'
1740
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1741
            varname='P:+1DP'
1742
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1743
            varname='P:-1DP'
1744
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1745
 
1746
            call calc_DTDP (traint(j,k,ncol+i), traint(j,k,ind1), &
1747
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1748
 
1749
         ! Vertical derivative of TH (DTHDP)
1750
         elseif  ( varsint(i+ncol).eq.'DTHDP' ) then
1751
 
1752
            varname='T:+1DP'
1753
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1754
            varname='T:-1DP'
1755
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1756
            varname='P:+1DP'
1757
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1758
            varname='P:-1DP'
1759
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1760
            varname='P'
1761
            call list2ind (ind5,varname,varsint,fok,ncol+ntrace1)
1762
            varname='T'
1763
            call list2ind (ind6,varname,varsint,fok,ncol+ntrace1)
1764
 
1765
            call calc_DTHDP (traint(j,k,ncol+i), traint(j,k,ind1), &
1766
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4),traint(j,k,ind5),traint(j,k,ind6) )
1767
 
1768
         ! Squared Brunt-Vaisäla frequency (NSQ)
1769
         elseif  ( varsint(i+ncol).eq.'NSQ' ) then
1770
 
1771
            varname='DTHDP'
1772
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1773
            varname='TH'
1774
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1775
            varname='RHO'
1776
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1777
 
1778
            call calc_NSQ (traint(j,k,ncol+i), traint(j,k,ind1), &
1779
                 traint(j,k,ind2),traint(j,k,ind3))
1780
 
1781
         ! Relative vorticity (RELVORT)
1782
         elseif  ( varsint(i+ncol).eq.'RELVORT' ) then
1783
 
1784
            varname='DUDY'
1785
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1786
            varname='DVDX'
1787
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1788
            varname='U'
1789
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1790
            varname='lat'
1791
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1792
 
1793
            call calc_RELVORT (traint(j,k,ncol+i), traint(j,k,ind1), &
1794
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4))
1795
 
1796
         ! Absolute vorticity (ABSVORT)
1797
         elseif  ( varsint(i+ncol).eq.'ABSVORT' ) then
1798
 
1799
            varname='DUDY'
1800
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1801
            varname='DVDX'
1802
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1803
            varname='U'
1804
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1805
            varname='lat'
1806
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1807
 
1808
            call calc_ABSVORT (traint(j,k,ncol+i), traint(j,k,ind1), &
1809
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4))
1810
 
1811
         ! Divergence (DIV)
1812
         elseif  ( varsint(i+ncol).eq.'DIV' ) then
1813
 
1814
            varname='DUDX'
1815
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1816
            varname='DVDY'
1817
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1818
            varname='V'
1819
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1820
            varname='lat'
1821
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1822
 
1823
            call calc_DIV (traint(j,k,ncol+i), traint(j,k,ind1), &
1824
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4))
1825
 
1826
         ! Deformation (DEF)
1827
         elseif  ( varsint(i+ncol).eq.'DEF' ) then
1828
 
1829
            varname='DUDX'
1830
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1831
            varname='DVDX'
1832
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1833
            varname='DUDY'
1834
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1835
            varname='DVDY'
1836
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1837
 
1838
            call calc_DEF (traint(j,k,ncol+i), traint(j,k,ind1), &
1839
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4))
1840
 
1841
         ! Potential Vorticity (PV)
1842
         elseif  ( varsint(i+ncol).eq.'PV' ) then
1843
 
1844
            varname='ABSVORT'
1845
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1846
            varname='DTHDP'
1847
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1848
            varname='DUDP'
1849
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1850
            varname='DVDP'
1851
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1852
            varname='DTHDX'
1853
            call list2ind (ind5,varname,varsint,fok,ncol+ntrace1)
1854
            varname='DTHDY'
1855
            call list2ind (ind6,varname,varsint,fok,ncol+ntrace1)
1856
 
1857
            call calc_PV (traint(j,k,ncol+i), traint(j,k,ind1), &
1858
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4),traint(j,k,ind5),traint(j,k,ind6) )
1859
 
1860
         ! Richardson number (RI)
1861
         elseif  ( varsint(i+ncol).eq.'RI' ) then
1862
 
1863
            varname='DUDP'
1864
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1865
            varname='DVDP'
1866
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1867
            varname='NSQ'
1868
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1869
            varname='RHO'
1870
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1871
 
1872
            call calc_RI (traint(j,k,ncol+i), traint(j,k,ind1), &
1873
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1874
 
1875
         ! Ellrod and Knapp's turbulence idicator (TI)
1876
         elseif  ( varsint(i+ncol).eq.'TI' ) then
1877
 
1878
            varname='DEF'
1879
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1880
            varname='DUDP'
1881
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1882
            varname='DVDP'
1883
            call list2ind (ind3,varname,varsint,fok,ncol+ntrace1)
1884
            varname='RHO'
1885
            call list2ind (ind4,varname,varsint,fok,ncol+ntrace1)
1886
 
1887
            call calc_TI (traint(j,k,ncol+i), traint(j,k,ind1), &
1888
                 traint(j,k,ind2),traint(j,k,ind3),traint(j,k,ind4) )
1889
 
1890
         ! Spherical distance from starting position (DIST0)
1891
         elseif  ( varsint(i+ncol).eq.'DIST0' ) then
1892
 
1893
            varname='lon'
1894
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1895
            varname='lat'
1896
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1897
 
1898
            call calc_DIST0 (traint(j,k,ncol+i), traint(j,k,ind1), &
1899
                 traint(j,k,ind2),traint(j,1,ind1),traint(j,1,ind2) )
1900
 
1901
         ! Spherical distance length of trajectory (DIST)
1902
         elseif  ( varsint(i+ncol).eq.'DIST' ) then
1903
 
1904
            varname='lon'
1905
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1906
            varname='lat'
1907
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1908
 
1909
            if ( k.eq.1 ) then
1910
               traint(j,k,ncol+i) = 0.
1911
            else
1912
               call calc_DIST0 (delta, traint(j,k  ,ind1), &
1913
                   traint(j,k  ,ind2),traint(j,k-1,ind1),traint(j,k-1,ind2) )
1914
               traint(j,k,ncol+i) = traint(j,k-1,ncol+i) + delta
1915
            endif
1916
 
1917
         ! Heading of the trajectory (HEAD)
1918
         elseif  ( varsint(i+ncol).eq.'HEAD' ) then
1919
 
1920
            varname='lon'
1921
            call list2ind (ind1,varname,varsint,fok,ncol+ntrace1)
1922
            varname='lat'
1923
            call list2ind (ind2,varname,varsint,fok,ncol+ntrace1)
1924
 
1925
            if (k.eq.ntim) then
1926
               traint(j,k,ncol+i) = mdv
1927
            else
1928
               call calc_HEAD (traint(j,k,ncol+i), &
1929
                    traint(j,k  ,ind1),traint(j,k  ,ind2),traint(j,k+1,ind1),traint(j,k+1,ind2) )
1930
            endif
1931
 
1932
 
1933
         ! Invalid tracing variable
1934
         else
1935
 
1936
            print*,' ERROR: invalid tracing variable ', trim(varsint(i+ncol))
1937
            stop
1938
 
1939
 
1940
         endif
1941
 
1942
      ! End loop over all trajectories and times
1943
      enddo
1944
      enddo
1945
 
1946
      ! Set the flag for a ready field/column
1947
      fok(ncol+i) = 1
1948
 
1949
 
1950
      ! Exit point for loop over all tracing fields
1951
 120   continue
1952
 
1953
   enddo
1954
 
1955
  ! --------------------------------------------------------------------
1956
  ! Write output to output trajectory file
1957
  ! --------------------------------------------------------------------
1958
 
1959
  ! Write status information
1960
  print*
1961
  print*,'---- WRITE OUTPUT TRAJECTORIES --------------------------'
1962
  print*
1963
 
1964
  ! Allocate memory for internal trajectories
1965
  allocate(traout(ntra,ntim,ncol+ntrace0),stat=stat)
1966
  if (stat.ne.0) print*,'*** error allocating array traout   ***'
1967
 
1968
  ! Copy input to output trajectory (apply scaling of output)
1969
  do i=1,ntra
1970
     do j=1,ntim
1971
        do k=1,ncol+ntrace0
1972
           if ( k.le.ncol ) then
1973
              traout(i,j,k) = traint(i,j,k)
1974
           elseif ( abs(traint(i,j,k)-mdv).gt.eps ) then
1975
              traout(i,j,k) = fac(k-ncol) * traint(i,j,k)
1976
           else
1977
              traout(i,j,k) = mdv
1978
           endif
1979
        enddo
1980
     enddo
1981
  enddo
1982
 
1983
  ! Set the variable names for output trajectory
1984
  do i=1,ncol+ntrace0
1985
     varsout(i)      = varsint(i)
1986
  enddo
1987
 
1988
  ! Write trajectories
1989
  call wopen_tra(fod,outfile,ntra,ntim,ncol+ntrace0, &
1990
       reftime,varsout,outmode)
1991
  call write_tra(fod,traout ,ntra,ntim,ncol+ntrace0,outmode)
1992
  call close_tra(fod,outmode)
1993
 
1994
  ! Write some status information, and end of program message
1995
  print*
1996
  print*,'---- STATUS INFORMATION --------------------------------'
1997
  print*
1998
  print*,' ok'
1999
  print*
2000
  print*,'              *** END OF PROGRAM TRACE ***'
2001
  print*,'========================================================='
2002
 
2003
 
2004
end program trace
2005
 
2006
 
2007
 
2008
! ******************************************************************
2009
! * SUBROUTINE SECTION                                             *
2010
! ******************************************************************
2011
 
2012
! ------------------------------------------------------------------
2013
! Add a variable to the list if not yet included in this list
2014
! ------------------------------------------------------------------
2015
 
2016
subroutine add2list (varname,list,nlist)
2017
 
2018
  implicit none
2019
 
2020
  ! Declaration of subroutine parameters
2021
  character(len=80) :: varname
2022
  character(len=80) :: list(200)
2023
  integer :: nlist
2024
 
2025
  ! Auxiliray variables
2026
  integer :: i,j
2027
  integer :: isok
2028
 
2029
  ! Expand the list, if necessary
2030
  isok = 0
2031
  do i=1,nlist
2032
     if ( list(i).eq.varname ) isok = 1
2033
  enddo
2034
  if ( isok.eq.0 ) then
2035
     nlist       = nlist + 1
2036
     list(nlist) = varname
2037
  endif
2038
 
2039
  ! Check for too large number of fields
2040
  if ( nlist.ge.200) then
2041
     print*,' ERROR: too many additional fields for tracing ...'
2042
     stop
2043
  endif
2044
 
2045
end subroutine add2list
2046
 
2047
 
2048
! ------------------------------------------------------------------
2049
! Get the index of a variable in the list
2050
! ------------------------------------------------------------------
2051
 
2052
subroutine list2ind (ind,varname,list,fok,nlist)
2053
 
2054
  implicit none
2055
 
2056
  ! Declaration of subroutine parameters
2057
  integer :: ind
2058
  character(len=80) :: varname
2059
  character(len=80) :: list(200)
2060
  integer :: fok(200)
2061
  integer :: nlist
2062
 
2063
  ! Auxiliray variables
2064
  integer :: i,j
2065
  integer :: isok
2066
 
2067
  ! Get the index - error message if not found
2068
  ind = 0
2069
  do i=1,nlist
2070
     if ( varname.eq.list(i) ) then
2071
        ind = i
2072
        goto 100
2073
     endif
2074
  enddo
2075
 
2076
  if ( ind.eq.0) then
2077
     print*
2078
     print*,' ERROR: cannot find ',trim(varname),' in list ...'
2079
     do i=1,nlist
2080
        print*,i,trim(list(i))
2081
     enddo
2082
     print*
2083
     stop
2084
  endif
2085
 
2086
  ! Exit point
2087
 100   continue
2088
 
2089
  ! Check whether the field/column is ready
2090
  if ( fok(ind).eq.0 ) then
2091
     print*
2092
     print*,' ERROR: unresolved dependence : ',trim(list(ind))
2093
     print*
2094
     stop
2095
  endif
2096
 
2097
end subroutine list2ind
2098
 
2099
 
2100
! ------------------------------------------------------------------
2101
! Split the variable name into name, shift and direction
2102
! ------------------------------------------------------------------
2103
 
2104
subroutine splitvar (tvar,shift_val,shift_dir)
2105
 
2106
  implicit none
2107
 
2108
  ! Declaration of subroutine parameters
2109
  character(len=80) :: tvar
2110
  real :: shift_val
2111
  character(len=80) :: shift_dir
2112
 
2113
  ! Auxiliary variables
2114
  integer :: i,j
2115
  integer :: icolon,inumber
2116
  character(len=80) :: name
2117
  character :: ch
2118
 
2119
  ! Save variable name
2120
  name = tvar
2121
 
2122
  ! Search for colon
2123
  icolon=0
2124
  do i=1,80
2125
     if ( (name(i:i).eq.':').and.(icolon.ne.0) ) goto 100
2126
     if ( (name(i:i).eq.':').and.(icolon.eq.0) ) icolon=i
2127
  enddo
2128
 
2129
  ! If there is a colon, split the variable name
2130
  if ( icolon.ne.0 ) then
2131
 
2132
     tvar = name(1:(icolon-1))
2133
 
2134
     do i=icolon+1,80
2135
        ch = name(i:i)
2136
        if ( ( ch.ne.'0' ).and. ( ch.ne.'1' ).and.( ch.ne.'2' ).and. &
2137
             ( ch.ne.'3' ).and. ( ch.ne.'4' ).and.( ch.ne.'5' ).and. &
2138
             ( ch.ne.'6' ).and. ( ch.ne.'7' ).and.( ch.ne.'8' ).and. &
2139
             ( ch.ne.'9' ).and. ( ch.ne.'+' ).and.( ch.ne.'-' ).and. &
2140
             ( ch.ne.'.' ).and. ( ch.ne.' ' )  ) then
2141
           inumber = i
2142
           exit
2143
        endif
2144
     enddo
2145
 
2146
     read(name( (icolon+1):(inumber-1) ),*) shift_val
2147
 
2148
     shift_dir = name(inumber:80)
2149
 
2150
  else
2151
 
2152
     shift_dir = 'nil'
2153
     shift_val = 0.
2154
 
2155
  endif
2156
 
2157
  return
2158
 
2159
  ! Error handling
2160
 100   continue
2161
 
2162
  print*,' ERROR: cannot split variable name ',trim(tvar)
2163
  stop
2164
 
2165
end subroutine splitvar