Subversion Repositories lagranto.wrf

Rev

Rev 21 | Details | Compare with Previous | Last modification | View Log | RSS feed

Rev Author Line No. Line
2 michaesp 1
 
2
PROGRAM trace_label_circle
3
 
4
  ! ********************************************************************
5
  ! *                                                                  *
6
  ! * Trace fields along trajectories                                  *
7
  ! *                                                                  *
8
  ! * Heini Wernli       first version:       April 1993               *
9
  ! * Michael Sprenger   major upgrade:       2008-2009                *
10
  ! * Sebastian Schemm WRF                                             *
11
  ! ********************************************************************
12
 
13
  implicit none
14
 
15
  ! --------------------------------------------------------------------
16
  ! Declaration of parameters
17
  ! --------------------------------------------------------------------
18
 
19
  ! Maximum number of levels for input files
20
  integer :: nlevmax
21
  parameter (nlevmax=100)
22
 
23
  ! Maximum number of input files (dates, length of trajectories)
24
  integer :: ndatmax
25
  parameter (ndatmax=500)
26
 
27
  ! Numerical epsilon (for float comparison)
28
  real :: eps
29
  parameter (eps=0.001)
20 michaesp 30
  real         mdv                              ! missing data value
31
  parameter    (mdv=-999.)
2 michaesp 32
 
33
  ! Prefix for primary and secondary fields
34
  character :: charp
35
  character :: chars
36
  parameter (charp='P')
37
  parameter (chars='S')
38
 
39
  ! --------------------------------------------------------------------
40
  ! Declaration of variables
41
  ! --------------------------------------------------------------------
42
 
43
  ! Input and output format for trajectories (see iotra.f)
44
  integer :: inpmode
45
  integer :: outmode
46
 
47
  ! Input parameters
48
  character(len=80) :: inpfile         ! Input trajectory file
49
  character(len=80) :: outfile         ! Output trajectory file
50
  integer :: ntra                      ! Number of trajectories
51
  integer :: ncol                      ! Number of columns (including time, lon, lat, p)
52
  integer :: ntim                      ! Number of times per trajectory
53
  integer :: ntrace0                   ! Number of trace variables
54
  character(len=80) :: tvar0(200)      ! Tracing variable (with mode specification)
55
  character(len=80) :: tvar(200)       ! Tracing variable name (only the variable)
56
  character(len=1)  :: tfil(200)       ! Filename prefix
57
  real :: fac(200)                     ! Scaling factor
58
  integer :: compfl(200)               ! Computation flag (1=compute)
59
  integer :: numdat                    ! Number of input files
23 michaesp 60
  character(len=13) :: dat(ndatmax)    ! Dates of input files
2 michaesp 61
  real :: timeinc                      ! Time increment between input files
62
  real :: tst                          ! Time shift of start relative to first data file
63
  real :: ten                          ! Time shift of end relatiev to first data file
64
  character(len=20) :: startdate       ! First time/date on trajectory
65
  character(len=20) :: enddate         ! Last time/date on trajectory
66
  character(len=80) :: timecheck       ! Either 'yes' or 'no'
67
  character(len=80) :: intmode         ! Interpolation mode ('normal', 'nearest')
68
 
69
  ! Trajectories
70
  real,allocatable, dimension (:,:,:) :: trainp          ! Input trajectories (ntra,ntim,ncol)
71
  real,allocatable, dimension (:,:,:) :: traint          ! Internal trajectories (ntra,ntim,ncol+ntrace0)
72
  real,allocatable, dimension (:,:,:) :: traout          ! Output trajectories (ntra,ntim,ncol+ntrace0)
73
  integer :: reftime(6)                                  ! Reference date
74
  character(len=80) :: varsinp(100)                      ! Field names for input trajectory
75
  character(len=80) :: varsint(100)                      ! Field names for internal trajectory
76
  character(len=80) :: varsout(100)                      ! Field names for output trajectory
77
  integer :: fid,fod                                     ! File identifier for inp and out trajectories
78
  real :: x0,y0,p0                                       ! Position of air parcel (physical space)
79
  real :: reltpos0                                       ! Relative time of air parcel
80
  real :: xind,yind,pind                                 ! Position of air parcel (grid space)
81
  integer :: fbflag                                      ! Flag for forward (1) or backward (-1) trajectories
82
  integer :: fok(100)                                    ! Flag whether field is ready
83
 
84
  ! Meteorological fields
85
  real,allocatable, dimension (:)     :: spt0,spt1       ! Surface pressure
86
  real,allocatable, dimension (:)     :: p3t0,p3t1       ! 3d-pressure
87
  real,allocatable, dimension (:)     :: f3t0,f3t1       ! 3d field for tracing
88
  character(len=80) :: svars(100)                        ! List of variables on S file
89
  character(len=80) :: pvars(100)                        ! List of variables on P file
90
  integer :: n_svars                                     ! Number of variables on S file
91
  integer :: n_pvars                                     ! Number of variables on P file
92
 
93
  ! Grid description
94
  real :: pollon,pollat   ! Longitude/latitude of pole
95
  real :: xmin,xmax       ! Zonal grid extension
96
  real :: ymin,ymax       ! Meridional grid extension
97
  integer :: nx,ny,nz     ! Grid dimensions
98
  real :: dx,dy           ! Horizontal grid resolution
99
  integer :: hem          ! Flag for hemispheric domain
100
  integer :: per          ! Flag for periodic domain
101
  real :: stagz           ! Vertical staggering
102
 
103
  ! Auxiliary variables
104
  integer :: i,j,k,l,m,n
105
  real :: rd
106
  character(len=80) :: filename,varname
107
  real :: time0,time1,reltpos
108
  integer :: itime0,itime1
109
  integer :: stat
110
  real :: tstart
111
  integer :: iloaded0,iloaded1
112
  real :: f0
113
  real :: frac
114
  real :: tload,tfrac
115
  integer :: isok
116
  character :: ch
117
  integer :: ind
118
  integer :: ind1,ind2,ind3,ind4,ind5
119
  integer :: ind6,ind7,ind8,ind9,ind0
120
  integer :: noutside
121
  real :: delta
122
  integer :: itrace0
123
  character(len=80) :: string
124
 
125
  ! Externals
126
  real :: int_index4
127
  external int_index4
128
  real :: sdis   
129
  external sdis 
130
 
131
  ! --------------------------------------------------------------------
132
  ! Start of program, Read parameters, get grid parameters
133
  ! --------------------------------------------------------------------
134
 
135
  ! Write start message
136
  print*,'========================================================='
137
  print*,'              *** START OF PROGRAM TRACE ***'
138
  print*
139
 
140
  ! Read parameters
141
  open(10,file='trace.param')
142
   read(10,*) inpfile
143
   read(10,*) outfile
144
   read(10,*) startdate
145
   read(10,*) enddate
146
   read(10,*) fbflag
147
   read(10,*) numdat
148
   if ( fbflag.eq.1) then
149
      do i=1,numdat
23 michaesp 150
         read(10,'(a)') dat(i)
2 michaesp 151
      enddo
152
   else
153
      do i=numdat,1,-1
23 michaesp 154
         read(10,'(a)') dat(i)
2 michaesp 155
      enddo
156
   endif
157
   read(10,*) timeinc
158
   read(10,*) tst
159
   read(10,*) ten
160
   read(10,*) ntra
161
   read(10,*) ntim
162
   read(10,*) ncol
163
   read(10,*) ntrace0
164
   do i=1,ntrace0
165
      read(10,*) tvar(i), fac(i), compfl(i), tfil(i)
166
   enddo
167
   read(10,*) n_pvars
168
   do i=1,n_pvars
169
      read(10,*) pvars(i)
170
   enddo
171
   read(10,*) n_svars
172
   do i=1,n_svars
173
      read(10,*) svars(i)
174
   enddo
175
   read(10,*) timecheck
176
   read(10,*) intmode
177
  close(10)
178
 
179
  ! Remove commented tracing fields
180
  itrace0 = 1
181
  do while ( itrace0.le.ntrace0)
182
     string = tvar(itrace0)
183
     if ( string(1:1).eq.'#' ) then
184
        do i=itrace0,ntrace0-1
185
           tvar(i)   = tvar(i+1)
186
           fac(i)    = fac(i+1)
187
           compfl(i) = compfl(i+1)
188
           tfil(i)   = tfil(i+1)
189
        enddo
190
        ntrace0 = ntrace0 - 1
191
     else
192
        itrace0 = itrace0 + 1
193
     endif
194
  enddo
195
 
196
  ! Save the tracing variable (including all mode specifications)
197
  do i=1,ntrace0
198
     tvar0(i) = tvar(i)
199
  enddo
200
 
201
  ! Set the formats of the input and output files
202
  call mode_tra(inpmode,inpfile)
203
  if (inpmode.eq.-1) inpmode=1
204
  call mode_tra(outmode,outfile)
205
  if (outmode.eq.-1) outmode=1
206
 
207
  ! Convert time shifts <tst,ten> from <hh.mm> into fractional time
208
  call hhmm2frac(tst,frac)
209
  tst = frac
210
  call hhmm2frac(ten,frac)
211
  ten = frac
212
 
213
  ! Set the time for the first data file (depending on forward/backward mode)
214
  if (fbflag.eq.1) then
215
    tstart = -tst
216
  else
217
    tstart = tst
218
  endif
219
 
220
  ! Read the constant grid parameters (nx,ny,nz,xmin,xmax,ymin,ymax,pollon,pollat)
221
  ! The negative <-fid> of the file identifier is used as a flag for parameter retrieval
222
  filename = charp//dat(1)
223
  varname  = 'U'
224
  call input_open (fid,filename)
225
  call input_grid_wrf(fid,xmin,xmax,ymin,ymax,dx,dy,nx,ny,nz)
226
  call input_close(fid)
227
 
228
  ! Allocate memory for some meteorological arrays
229
  allocate(spt0(nx*ny),stat=stat)
230
  if (stat.ne.0) print*,'*** error allocating array spt0 ***'   ! Surface pressure
231
  allocate(spt1(nx*ny),stat=stat)
232
  if (stat.ne.0) print*,'*** error allocating array spt1 ***'
233
  allocate(p3t0(nx*ny*nz),stat=stat)
234
  if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Pressure
235
  allocate(p3t1(nx*ny*nz),stat=stat)
236
  if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
237
  allocate(f3t0(nx*ny*nz),stat=stat)
238
  if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Tracing field
239
  allocate(f3t1(nx*ny*nz),stat=stat)
240
  if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
241
 
242
  ! Get memory for trajectory arrays
243
  allocate(trainp(ntra,ntim,ncol),stat=stat)
244
  if (stat.ne.0) print*,'*** error allocating array tra      ***'
245
 
246
  ! Write some status information
247
  print*,'---- INPUT PARAMETERS -----------------------------------'
248
  print*
249
  print*,'  Input trajectory file  : ',trim(inpfile)
250
  print*,'  Output trajectory file : ',trim(outfile)
251
  print*,'  Format of input file   : ',inpmode
252
  print*,'  Format of output file  : ',outmode
253
  print*,'  Forward/backward       : ',fbflag
254
  print*,'  #tra                   : ',ntra
255
  print*,'  #col                   : ',ncol
256
  print*,'  #tim                   : ',ntim
257
  print*,'  No time check          : ',trim(timecheck)
258
  print*,'  Interpolation mode     : ',trim(intmode)
259
  do i=1,ntrace0
260
     if (compfl(i).eq.0) then
261
        print*,'  Tracing field          : ', trim(tvar(i)), fac(i), ' 0 ', tfil(i)
262
     else
263
        print*,'  Tracing field          : ', trim(tvar(i)), fac(i), '  1 ', tfil(i)
264
     endif
265
  enddo
266
  print*
267
  print*,'---- INPUT DATA FILES -----------------------------------'
268
  print*
269
  call frac2hhmm(tstart,tload)
270
  print*,'  Time of 1st data file  : ',tload
271
  print*,'  #input files           : ',numdat
272
  print*,'  time increment         : ',timeinc
273
  call frac2hhmm(tst,tload)
274
  print*,'  Shift of start         : ',tload
275
  call frac2hhmm(ten,tload)
276
  print*,'  Shift of end           : ',tload
277
  print*,'  First/last input file  : ',trim(dat(1)), ' ... ', trim(dat(numdat))
278
  print*,'  Primary variables      : ',trim(pvars(1))
279
  do i=2,n_pvars
280
     print*,'                         : ',trim(pvars(i))
281
  enddo
282
  if ( n_svars.ge.1 ) then
283
     print*,'  Secondary variables    : ',trim(svars(1))
284
     do i=2,n_svars
285
        print*,'                         : ',trim(svars(i))
286
     enddo
287
  endif
288
  print*
289
  print*,'---- CONSTANT GRID PARAMETERS ---------------------------'
290
  print*
291
  print*,'  xmin,xmax     : ',xmin,xmax
292
  print*,'  ymin,ymax     : ',ymin,ymax
293
  print*,'  dx,dy         : ',dx,dy
294
  print*,'  pollon,pollat : ',pollon,pollat
295
  print*,'  nx,ny,nz      : ',nx,ny,nz
296
  print*,'  per, hem      : ',per,hem
297
  print*
298
 
299
  ! --------------------------------------------------------------------
300
  ! Load the input trajectories
301
  ! --------------------------------------------------------------------
302
 
303
  ! Read the input trajectory file
304
  call ropen_tra(fid,inpfile,ntra,ntim,ncol,reftime,varsinp,inpmode)
305
  call read_tra (fid,trainp,ntra,ntim,ncol,inpmode)
306
  call close_tra(fid,inpmode)
307
 
308
  ! Check that first four columns correspond to time,x,y,z
309
  if ( (varsinp(1).ne.'time' ).or. &
310
       (varsinp(2).ne.'x'    ).or. &
311
       (varsinp(3).ne.'y'    ).or. &
312
       (varsinp(4).ne.'z'   ) )    &
313
  then
314
     print*,' ERROR: problem with input trajectories ...'
315
     stop
316
  endif
317
  varsinp(1) = 'time'
318
  varsinp(2) = 'x'
319
  varsinp(3) = 'y'
320
  varsinp(4) = 'z'
321
 
322
  ! Transform start coordinates from index space to WRF grid
323
  do i=1,ntra
324
     do j=1,ntim
20 michaesp 325
         if ( ( abs(trainp(i,j,2)-mdv).gt.eps).and.( abs(trainp(i,j,3)-mdv).gt.eps) ) then
326
            trainp(i,j,2) = xmin + ( trainp(i,j,2) - 1. ) * dx
327
            trainp(i,j,3) = ymin + ( trainp(i,j,3) - 1. ) * dy
328
         endif
2 michaesp 329
     enddo
330
  enddo
331
 
332
  ! Write some status information of the input trajectories
333
  print*,'---- INPUT TRAJECTORIES ---------------------------------'
334
  print*
335
  print*,' Start date             : ',trim(startdate)
336
  print*,' End date               : ',trim(enddate)
337
  print*,' Reference time (year)  : ',reftime(1)
338
  print*,'                (month) : ',reftime(2)
339
  print*,'                (day)   : ',reftime(3)
340
  print*,'                (hour)  : ',reftime(4)
341
  print*,'                (min)   : ',reftime(5)
342
  print*,' Time range (min)       : ',reftime(6)
343
  do i=1,ncol
344
     print*,' Var                    :',i,trim(varsinp(i))
345
  enddo
346
  print*
347
 
348
  ! Check that first time is 0 - otherwise the tracing will produce
349
  ! wrong results because later in the code only absolute times are
350
  ! considered: <itime0   = int(abs(tfrac-tstart)/timeinc) + 1>. This
351
  ! will be changed in a future version.
352
  if ( abs( trainp(1,1,1) ).gt.eps ) then
353
     print*,' ERROR: First time of trajectory must be 0, i.e. '
354
     print*,'     correspond to the reference date. Otherwise'
355
     print*,'     the tracing will give wrong results... STOP'
356
     stop
357
  endif
358
 
359
  ! Save the full variable name (including shift specification)
360
  do i=1,ncol
361
     varsint(i)      = varsinp(i)
362
  enddo
363
  do i=1,ntrace0
364
     varsint(i+ncol) = tvar(i)
365
  enddo
366
 
367
  ! Split the variable name and set flags
368
  do i=1,ntrace0
369
 
370
     ! Set the prefix of the file name
371
     if ( compfl(i).eq.0  ) then
372
        tfil(i)=' '
373
        do j=1,n_pvars
374
           if ( tvar(i).eq.pvars(j) ) tfil(i)=charp
375
        enddo
376
        do j=1,n_svars
377
           if ( tvar(i).eq.svars(j) ) tfil(i)=chars
378
        enddo
379
     elseif ( tvar(i).eq.'Z' ) then
380
        tfil(i) = 'P'
381
     elseif ( tvar(i).eq.'ZB' ) then
382
        tfil(i) = 'P'
383
     else
384
        tfil(i) = '*' 
385
     endif
386
 
387
  enddo
388
 
389
  ! Write status information
390
  print*
391
  print*,'---- COMPLETE TABLE FOR TRACING -------------------------'
392
  print*
393
  do i=1,ntrace0
394
      write(*,'(i4,a4,a8,10x,8x,3x,a1,i5)') &
395
             i,' : ',trim(tvar(i)),tfil(i),compfl(i)
396
  enddo
397
 
398
  ! Allocate memory for internal trajectories
399
  allocate(traint(ntra,ntim,ncol+ntrace0),stat=stat)
400
  if (stat.ne.0) print*,'*** error allocating array traint   ***'
401
 
402
  ! Copy input to output trajectory
403
  do i=1,ntra
404
     do j=1,ntim
405
        do k=1,ncol
406
           traint(i,j,k)=trainp(i,j,k)
407
        enddo
408
     enddo
409
  enddo
410
 
411
  ! --------------------------------------------------------------------
412
  ! Trace the fields (fields available on input files)
413
  ! --------------------------------------------------------------------
414
 
415
  print*
416
  print*,'---- TRACING FROM PRIMARY AND SECONDARY DATA FILES ------'
417
 
418
  ! Loop over all tracing fields
419
  do i=1,ntrace0
420
 
421
      ! Write some status information
422
      print*
423
      print*,' Now tracing             : ', trim(tvar(i)),' ',trim(tfil(i))
424
 
425
      ! Reset flags for load manager
426
      iloaded0 = -1
427
      iloaded1 = -1
428
 
429
      ! Reset the counter for fields outside domain
430
      noutside = 0
431
 
432
      ! Loop over all times
433
      do j=1,ntim
434
 
435
         ! Convert trajectory time from hh.mm to fractional time
436
         call hhmm2frac(trainp(1,j,1),tfrac)
437
 
438
         ! Get the times which are needed
439
         itime0   = int(abs(tfrac-tstart)/timeinc) + 1
440
         time0    = tstart + fbflag * real(itime0-1) * timeinc
441
         itime1   = itime0 + 1
442
         time1    = time0 + fbflag * timeinc
443
         if ( itime1.gt.numdat ) then
444
            itime1 = itime0
445
            time1  = time0
446
         endif
447
 
448
         ! Load manager: Check whether itime0 can be copied from itime1
449
         if ( itime0.eq.iloaded1 ) then
450
            f3t0     = f3t1
451
            p3t0     = p3t1
452
            spt0     = spt1
453
            iloaded0 = itime0
454
         endif
455
 
456
         ! Load manager: Check whether itime1 can be copied from itime0
457
         if ( itime1.eq.iloaded0 ) then
458
            f3t1     = f3t0
459
            p3t1     = p3t0
460
            spt1     = spt0
461
            iloaded1 = itime1
462
         endif
463
 
464
 
465
         ! Load manager:  Load first time (tracing variable and grid)
466
         if ( itime0.ne.iloaded0 ) then
467
 
468
            filename = tfil(i)//dat(itime0)
469
            call frac2hhmm(time0,tload)
470
            varname  = tvar(i)
471
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
472
            call input_open (fid,filename)
473
 
474
	        call input_var_wrf(fid,varname,f3t0,nx,ny,nz)	! field to trace
475
 
476
	        varname='geopot'					            ! geopot.height
477
	        call input_var_wrf(fid,varname,p3t0,nx,ny,nz)
478
 
479
	        varname='geopots'					            ! surface geopot.height
480
	        call input_var_wrf(fid,varname,spt0,nx,ny,1 )
481
 
482
            call input_close(fid)
483
 
484
            iloaded0 = itime0
485
 
486
         endif
487
 
488
         ! Load manager: Load second time (tracing variable and grid)
489
         if ( itime1.ne.iloaded1 ) then
490
 
491
            filename = tfil(i)//dat(itime1)
492
            call frac2hhmm(time1,tload)
493
            varname  = tvar(i)
494
            write(*,'(a23,a20,a3,a5,f7.2)') '    ->  loading          : ', trim(filename),'  ',trim(varname),tload
495
            call input_open (fid,filename)
496
 
497
            call input_var_wrf(fid,varname,f3t1,nx,ny,nz)	        ! field to trace
498
 
499
	        varname='geopot'					                    ! geopot.height
500
	        call input_var_wrf(fid,varname,p3t1,nx,ny,nz)
501
 
21 michaesp 502
	        varname='geopots'					                    ! surface geopot.height 
2 michaesp 503
	        call input_var_wrf(fid,varname,spt1,nx,ny,1)
504
 
505
            call input_close(fid)
506
 
507
            iloaded1 = itime1
508
 
509
         endif
510
 
511
         ! Loop over all trajectories
512
         do k=1,ntra
513
 
514
            ! Set the horizontal position where to interpolate to
515
            x0       = traint(k,j,2)                          ! Longitude
21 michaesp 516
            y0       = traint(k,j,3)
517
                                   ! Latitude
518
            ! Set the relative time
519
            call hhmm2frac(traint(k,j,1),tfrac)
520
            reltpos0 = fbflag * (tfrac-time0)/timeinc
2 michaesp 521
 
522
            ! Set the vertical position where to interpolate to: 
523
            if ( nz.gt.1 ) then
524
               p0 = traint(k,j,4)                            ! Pressure (3D tracing)
525
            else
526
               p0 = 1                                        ! Lowest level (2D tracing)
527
            endif
528
 
529
            ! Get the index where to interpolate (x0,y0,p0)
530
            if ( (abs(x0-mdv).gt.eps).and. (abs(y0-mdv).gt.eps) ) then
531
               call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0, &
532
                    p3t0,p3t1,spt0,spt1,3,nx,ny,nz,xmin,ymin,dx,dy,mdv)
533
            else
534
               xind = mdv
535
               yind = mdv
536
               pind = mdv
537
            endif
538
 
539
 
540
            ! Check if point is within grid (keep indices if ok)
541
            if ( (xind.ge.1.).and.(xind.le.real(nx)).and. &
542
                 (yind.ge.1.).and.(yind.le.real(ny)).and. &
543
                 (pind.ge.1.).and.(pind.le.real(nz)) )    &
544
            then
545
		           xind = xind
546
		           yind = yind
547
		           pind = pind
548
 
549
            endif
550
 
551
            ! ------------------------ NEAREST mode ------------------------------- 
552
 
553
            if ( intmode.eq.'nearest') then
554
 
555
               xind = real( nint(xind) )
556
               yind = real( nint(yind) )
557
               pind = real( nint(pind) )
558
 
559
               if ( xind.lt.1.  ) xind = 1.
560
               if ( xind.gt.nx  ) xind = real(nx)
561
               if ( yind.lt.1.  ) yind = 1.
562
               if ( yind.gt.ny  ) yind = real(ny)
563
 
564
               if ( pind.lt.1.  ) pind = 1.
565
               if ( pind.gt.nz  ) pind = real(nz)
566
 
567
               if ( abs(reltpos0).ge.eps ) then
568
                  print*,'ERROR (nearest): reltpos != 0',reltpos0
569
                  stop
570
               endif
571
 
572
               ! interpolate
573
               f0 = int_index4(f3t0,f3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
574
 
575
            ! ------------------------ NORMAL mode -------------------------------
576
            else 
577
 
578
               f0 = int_index4(f3t0,f3t1,nx,ny,nz,xind,yind,pind,reltpos0,mdv)
21 michaesp 579
 
2 michaesp 580
            endif
581
 
582
            ! Save the new field
583
            if ( abs(f0-mdv).gt.eps) then
584
               traint(k,j,ncol+i) = f0
585
            else
586
               traint(k,j,ncol+i) = mdv
587
            endif
588
 
589
         enddo ! end loop over all trajectories
590
 
591
      enddo ! end loop over all times
592
 
593
      ! Exit point for loop over all tracing variables
594
 110   continue
595
 
21 michaesp 596
  enddo ! end loop over all tracing variables
2 michaesp 597
 
598
  ! --------------------------------------------------------------------
599
  ! Write output to output trajectory file
600
  ! --------------------------------------------------------------------
601
 
602
  ! Write status information
603
  print*
604
  print*,'---- WRITE OUTPUT TRAJECTORIES --------------------------'
605
  print*
606
 
607
  ! Allocate memory for internal trajectories
608
  allocate(traout(ntra,ntim,ncol+ntrace0),stat=stat)
609
  if (stat.ne.0) print*,'*** error allocating array traout   ***'
610
 
611
  ! Copy input to output trajectory (apply scaling of output)
612
  do i=1,ntra
613
     do j=1,ntim
614
        do k=1,ncol+ntrace0
615
           if ( k.le.ncol ) then
616
              traout(i,j,k) = traint(i,j,k)
617
           elseif ( abs(traint(i,j,k)-mdv).gt.eps ) then
618
              traout(i,j,k) = fac(k-ncol) * traint(i,j,k)
619
           else
620
              traout(i,j,k) = mdv
621
           endif
622
        enddo
623
     enddo
624
  enddo
625
 
626
  ! Set the variable names for output trajectory
627
  do i=1,ncol+ntrace0
628
     varsout(i)      = varsint(i)
629
  enddo
630
 
631
 ! Transform coordinates into index space
632
   do i=1,ntra
633
     do j=1,ntim
20 michaesp 634
 
635
         if ( ( abs(traout(i,j,2)-mdv).gt.eps ).and.( abs(traout(i,j,3)-mdv).gt.eps ) ) then
636
            traout(i,j,2) = ( traout(i,j,2) - xmin ) / dx + 1.
637
            traout(i,j,3) = ( traout(i,j,3) - ymin ) / dy + 1.
638
         endif
639
 
2 michaesp 640
     enddo
641
  enddo
642
 
643
  ! Write trajectories
644
  call wopen_tra(fod,outfile,ntra,ntim,ncol+ntrace0, &
645
       reftime,varsout,outmode)
646
  call write_tra(fod,traout ,ntra,ntim,ncol+ntrace0,outmode)
647
  call close_tra(fod,outmode)
648
 
649
  ! Write some status information, and end of program message
650
  print*
651
  print*,'---- STATUS INFORMATION --------------------------------'
652
  print*
653
  print*,' ok'
654
  print*
655
  print*,'              *** END OF PROGRAM TRACE ***'
656
  print*,'========================================================='
657
 
658
 
659
end program trace_label_circle
660