Subversion Repositories lagranto.ecmwf

Rev

Rev 44 | Only display areas with differences | Ignore whitespace | Details | Blame | Last modification | View Log | RSS feed

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