Subversion Repositories lagranto.ocean

Rev

Details | Last modification | View Log | RSS feed

Rev Author Line No. Line
3 michaesp 1
      PROGRAM trace
2
 
3
C     ********************************************************************
4
C     *                                                                  *
5
C     * Pseudo-lidar plots along trajectories                             *
6
C     *                                                                  *
7
C     * Heini Wernli       first version:       April 1993               *
8
C     * Michael Sprenger   major upgrade:       2008-2009                *
9
C     *                                                                  *
10
C     ********************************************************************
11
 
12
      implicit none
13
 
14
c     --------------------------------------------------------------------
15
c     Declaration of parameters
16
c     --------------------------------------------------------------------
17
 
18
c     Maximum number of levels for input files
19
      integer   nlevmax
20
      parameter (nlevmax=100)
21
 
22
c     Maximum number of input files (dates, length of trajectories)
23
      integer   ndatmax
24
      parameter (ndatmax=500)
25
 
26
c     Numerical epsilon (for float comparison)
27
      real      eps
28
      parameter (eps=0.001)
29
 
30
c     Conversion factors
31
      real      pi180                                   ! deg -> rad
32
      parameter (pi180=3.14159/180.)
33
      real      deg2km                                  ! deg -> km (at equator)
34
      parameter (deg2km=111.)
35
 
36
c     Prefix for primary and secondary fields
37
      character charp
38
      character chars
39
      parameter (charp='P')
40
      parameter (chars='S')
41
 
42
c     --------------------------------------------------------------------
43
c     Declaration of variables
44
c     --------------------------------------------------------------------
45
 
46
c     Input and output format for trajectories (see iotra.f)
47
      integer   inpmode
48
 
49
c     Input parameters
50
      character*80                           inpfile         ! Input trajectory file
51
      character*80                           outfile         ! Output netCDF file
52
      character*80                           outmode         ! Output mode (sum,mean)
53
      integer                                ntra            ! Number of trajectories
54
      integer                                ncol            ! Number of columns (including time, lon, lat, p)
55
      integer                                ntim            ! Number of times per trajectory
56
      integer                                ntrace0         ! Number of trace variables
57
      character*80                           tvar(200)       ! Tracing variable name (only the variable)
58
      character*1                            tfil(200)       ! Filename prefix 
59
      real                                   fac(200)        ! Scaling factor 
60
      integer                                compfl(200)     ! Computation flag (1=compute)
61
      integer                                numdat          ! Number of input files
62
      character*11                           dat(ndatmax)    ! Dates of input files
63
      real                                   timeinc         ! Time increment between input files
64
      real                                   tst             ! Time shift of start relative to first data file
65
      real                                   ten             ! Time shift of end relatiev to first data file  
66
      character*20                           startdate       ! First time/date on trajectory
67
      character*20                           enddate         ! Last time/date on trajectory
68
      character*80                           timecheck       ! Either 'yes' or 'no'
69
      character*80                           intmode         ! Interpolation mode ('normal', 'nearest')
70
	  real                                   pmin,pmax       ! Pressure range for output grid
71
	  integer                                npre            ! Number of pressure levels in output grid
72
	  character*80                           centering       ! Centering around trajectory position ('yes','no')
73
	  character*80                       direction       ! Direction of lidar (vertical,lat,lon,normal)
74
      character*80                           dumpcoord       ! Dumping coordinates ('yes','no')
75
 
76
c     Trajectories
77
      real,allocatable, dimension (:,:,:) :: trainp                ! Input trajectories (ntra,ntim,ncol)
78
      integer                                reftime(6)            ! Reference date
79
      character*80                           varsinp(100)          ! Field names for input trajectory
80
      integer                                fid,fod               ! File identifier for inp and out trajectories
81
      real                                   x0_tra,y0_tra,p0_tra  ! Position of air parcel (physical space)
82
      real                                   reltpos0              ! Relative time of air parcel
83
      real                                   xind,yind,pind        ! Position of air parcel (grid space)
84
      integer                                fbflag                ! Flag for forward (1) or backward (-1) trajectories
85
 
86
c     Meteorological fields from input file
87
      real,allocatable, dimension (:)     :: spt0,spt1       ! Surface pressure
88
      real,allocatable, dimension (:)     :: p3t0,p3t1       ! 3d-pressure 
89
      real,allocatable, dimension (:)     :: f3t0,f3t1       ! 3d field for tracing 
90
      character*80                           svars(100)      ! List of variables on S file
91
      character*80                           pvars(100)      ! List of variables on P file
92
      integer                                n_svars         ! Number of variables on S file
93
      integer                                n_pvars         ! Number of variables on P file
94
 
95
c     Input grid description
96
      real                                   pollon,pollat   ! Longitude/latitude of pole
97
      real                                   ak(100)         ! Vertical layers and levels
98
      real                                   bk(100) 
99
      real                                   xmin,xmax       ! Zonal grid extension
100
      real                                   ymin,ymax       ! Meridional grid extension
101
      integer                                nx,ny,nz        ! Grid dimensions
102
      real                                   dx,dy           ! Horizontal grid resolution
103
      integer                                hem             ! Flag for hemispheric domain
104
      integer                                per             ! Flag for periodic domain
105
      real                                   stagz           ! Vertical staggering
106
      real                                   mdv             ! Missing data value
107
 
108
c	  Output grid  and fields
109
      real                                   levels(1000)    ! Ouput levels
110
      real                                   times (1000)    ! Output times
111
	  real,allocatable, dimension (:,:)   :: out_pos         ! Position of trajectories
112
	  real,allocatable, dimension (:,:)   :: out_val         ! Output lidar field
113
	  real,allocatable, dimension (:,:)   :: out_cnt         ! # output lidar sum ups
114
 
115
 
116
c     Auxiliary variables
117
      integer                                i,j,k,l,n
118
      real                                   rd
119
      character*80                           filename
120
      real                                   time0,time1,reltpos
121
      integer                                itime0,itime1
122
      integer                                stat
123
      real                                   tstart
124
      integer                                iloaded0,iloaded1
125
      real                                   f0
126
      real                                   frac
127
      real                                   tload,tfrac
128
      integer                                isok
129
      character                              ch
130
      integer                                ind
131
      integer                                ind1,ind2,ind3,ind4,ind5
132
      integer                                ind6,ind7,ind8,ind9,ind0
133
      integer                                noutside
134
      real                                   delta
135
      integer                                itrace0
136
      character*80                           string
137
      character*80                           cdfname
138
      character*80                           varname
139
      real                                   time
140
      character*80                           longname
141
      character*80                           unit
142
      integer                                ind_time
143
      integer                                ind_pre
144
      real                                   rlat,rlon
145
      real                                   x0,y0,p0
146
      real                                   vx0,vy0,vx1,vy1
147
      real                                   rotation,lon,lat
148
 
149
c     Externals 
150
      real                                   int_index4
151
      external                               int_index4
152
 
153
c     --------------------------------------------------------------------
154
c     Start of program, Read parameters, get grid parameters
155
c     --------------------------------------------------------------------
156
 
157
c     Write start message
158
c      print*,'========================================================='
159
      print*,'              *** START OF PROGRAM LIDAR ***'
160
      print*
161
c     Read parameters
162
      open(10,file='trace.param')
163
       read(10,*) inpfile
164
       read(10,*) outfile
165
       read(10,*) outmode
166
       read(10,*) startdate
167
       read(10,*) enddate 
168
       read(10,*) fbflag
169
       read(10,*) numdat
170
       if ( fbflag.eq.1) then
171
          do i=1,numdat
172
             read(10,'(a11)') dat(i)
173
          enddo
174
       else
175
          do i=numdat,1,-1
176
             read(10,'(a11)') dat(i)
177
          enddo
178
       endif
179
       read(10,*) timeinc
180
       read(10,*) tst
181
       read(10,*) ten
182
       read(10,*) ntra
183
       read(10,*) ntim
184
       read(10,*) ncol
185
       read(10,*) ntrace0
186
       do i=1,ntrace0
187
          read(10,*) tvar(i), fac(i), compfl(i), tfil(i)
188
       enddo
189
       read(10,*) n_pvars
190
       do i=1,n_pvars
191
          read(10,*) pvars(i)
192
       enddo
193
       read(10,*) n_svars
194
       do i=1,n_svars
195
          read(10,*) svars(i)
196
       enddo
197
       read(10,*) timecheck
198
       read(10,*) intmode
199
       read(10,*) pmin,pmax,npre
200
       read(10,*) centering
201
       read(10,*) direction
202
       read(10,*) dumpcoord
203
      close(10)
204
 
205
c     Check that the direction is ok
206
      if ( ( direction.ne.'vertical' ).and.
207
     >     ( direction.ne.'lat'      ).and.
208
     >     ( direction.ne.'lon'      ).and.
209
     >     ( direction.ne.'normal'   ) ) 
210
     >then 
211
         print*,' ERROR: invalid direction ',trim(direction)
212
         stop
213
      endif
214
 
215
c     Remove commented tracing fields
216
      itrace0 = 1
217
      do while ( itrace0.le.ntrace0) 
218
         string = tvar(itrace0)
219
         if ( string(1:1).eq.'#' ) then
220
            do i=itrace0,ntrace0-1
221
               tvar(i)   = tvar(i+1)
222
               fac(i)    = fac(i+1)
223
               compfl(i) = compfl(i+1)
224
               tfil(i)   = tfil(i+1)
225
            enddo
226
            ntrace0 = ntrace0 - 1
227
         else
228
            itrace0 = itrace0 + 1
229
         endif
230
      enddo
231
 
232
c     Set the formats of the input  files
233
      call mode_tra(inpmode,inpfile)
234
      if (inpmode.eq.-1) inpmode=1
235
 
236
C     Convert time shifts <tst,ten> from <hh.mm> into fractional time
237
      call hhmm2frac(tst,frac)
238
      tst = frac
239
      call hhmm2frac(ten,frac)
240
      ten = frac
241
 
242
c     Set the time for the first data file (depending on forward/backward mode)
243
      if (fbflag.eq.1) then
244
        tstart = -tst
245
      else
246
        tstart = tst
247
      endif
248
 
249
c     Read the constant grid parameters (nx,ny,nz,xmin,xmax,ymin,ymax,pollon,pollat)
250
c     The negative <-fid> of the file identifier is used as a flag for parameter retrieval  
251
c      filename = charp//dat(1)
252
      filename = tfil(1)//dat(1)
253
      varname  = tvar(1)
254
      call input_open (fid,filename)
255
      call input_grid (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,
256
     >                 tstart,pollon,pollat,rd,rd,nz,rd,rd,rd,timecheck)
257
      call input_close(fid)
258
 
259
C     Allocate memory for some meteorological arrays
260
      allocate(spt0(nx*ny),stat=stat)
261
      if (stat.ne.0) print*,'*** error allocating array spt0 ***'   ! Surface pressure
262
      allocate(spt1(nx*ny),stat=stat)
263
      if (stat.ne.0) print*,'*** error allocating array spt1 ***'
264
      allocate(p3t0(nx*ny*nz),stat=stat)
265
      if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Pressure
266
      allocate(p3t1(nx*ny*nz),stat=stat)
267
      if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
268
      allocate(f3t0(nx*ny*nz),stat=stat)
269
      if (stat.ne.0) print*,'*** error allocating array p3t0 ***'   ! Lidar field
270
      allocate(f3t1(nx*ny*nz),stat=stat)
271
      if (stat.ne.0) print*,'*** error allocating array p3t1 ***'
272
 
273
c	  Allocate memory for output field
274
	  allocate(out_pos(ntim,npre),stat=stat)
275
      if (stat.ne.0) print*,'*** error allocating array out_pos ***'
276
	  allocate(out_val(ntim,npre),stat=stat)
277
      if (stat.ne.0) print*,'*** error allocating array out_val ***'
278
	  allocate(out_cnt(ntim,npre),stat=stat)
279
      if (stat.ne.0) print*,'*** error allocating array out_cnt ***'
280
 
281
C     Get memory for trajectory arrays
282
      allocate(trainp(ntra,ntim,ncol),stat=stat)
283
      if (stat.ne.0) print*,'*** error allocating array tra      ***' 
284
 
285
c     Set the flags for periodic domains
286
      if ( abs(xmax-xmin-360.).lt.eps ) then
287
         per = 1
288
      elseif ( abs(xmax-xmin-360.+dx).lt.eps ) then
289
         per = 2
290
      else
291
         per = 0
292
      endif
293
 
294
C     Set logical flag for periodic data set (hemispheric or not)
295
      hem = 0
296
      if (per.eq.0.) then
297
         delta=xmax-xmin-360.
298
         if (abs(delta+dx).lt.eps) then               ! Program aborts: arrays must be closed
299
            print*,' ERROR: arrays must be closed... Stop'
300
         else if (abs(delta).lt.eps) then ! Periodic and hemispheric
301
           hem=1
302
           per=360.
303
        endif
304
      else                                            ! Periodic and hemispheric
305
         hem=1
306
      endif
307
 
308
c     Write some status information
309
      print*,'---- INPUT PARAMETERS -----------------------------------'
310
      print*
311
      print*,'  Input trajectory file  : ',trim(inpfile)
312
      print*,'  Format of input file   : ',inpmode
313
      print*,'  Output netCDF    file  : ',trim(outfile)
314
      print*,'  Format of output file  : ',trim(outmode)
315
      print*,'  Forward/backward       : ',fbflag
316
      print*,'  #tra                   : ',ntra
317
      print*,'  #col                   : ',ncol
318
      print*,'  #tim                   : ',ntim
319
      print*,'  No time check          : ',trim(timecheck)
320
      print*,'  Interpolation mode     : ',trim(intmode)
321
      do i=1,ntrace0
322
         if (compfl(i).eq.0) then
323
            print*,'  Tracing field          : ',
324
     >                 trim(tvar(i)), fac(i), ' 0 ', tfil(i)
325
         else
326
            print*,'  Tracing field          : ',
327
     >                trim(tvar(i)),' : online calc not supported'
328
         endif
329
      enddo
330
      print*,'  Output (pmin,pmax,n)   : ',pmin,pmax,npre
331
      print*,'  Centering              : ',trim(centering)
332
      print*,'  Orientation            : ',trim(direction)
333
      print*,'  Coordinate Dump        : ',trim(dumpcoord)
334
      print*
335
      print*,'---- INPUT DATA FILES -----------------------------------'
336
      print*
337
      call frac2hhmm(tstart,tload)
338
      print*,'  Time of 1st data file  : ',tload
339
      print*,'  #input files           : ',numdat
340
      print*,'  time increment         : ',timeinc
341
      call frac2hhmm(tst,tload)
342
      print*,'  Shift of start         : ',tload
343
      call frac2hhmm(ten,tload)
344
      print*,'  Shift of end           : ',tload
345
      print*,'  First/last input file  : ',trim(dat(1)),
346
     >                                     ' ... ',
347
     >                                     trim(dat(numdat)) 
348
      print*,'  Primary variables      : ',trim(pvars(1))
349
      do i=2,n_pvars
350
         print*,'                         : ',trim(pvars(i))
351
      enddo
352
      if ( n_svars.ge.1 ) then
353
         print*,'  Secondary variables    : ',trim(svars(1))
354
         do i=2,n_svars
355
            print*,'                         : ',trim(svars(i))
356
         enddo
357
      endif
358
      print*
359
      print*,'---- CONSTANT GRID PARAMETERS ---------------------------'
360
      print*
361
      print*,'  xmin,xmax     : ',xmin,xmax
362
      print*,'  ymin,ymax     : ',ymin,ymax
363
      print*,'  dx,dy         : ',dx,dy
364
      print*,'  pollon,pollat : ',pollon,pollat
365
      print*,'  nx,ny,nz      : ',nx,ny,nz
366
      print*,'  per, hem      : ',per,hem
367
      print*
368
 
369
c     --------------------------------------------------------------------
370
c     Load the input trajectories
371
c     --------------------------------------------------------------------
372
 
373
c     Read the input trajectory file
374
      call ropen_tra(fid,inpfile,ntra,ntim,ncol,reftime,varsinp,inpmode)
375
      call read_tra (fid,trainp,ntra,ntim,ncol,inpmode)
376
      call close_tra(fid,inpmode)
377
 
378
c     Check that first four columns correspond to time,lon,lat,p
379
      if ( (varsinp(1).ne.'time' ).or.
380
     >     (varsinp(2).ne.'xpos' ).and.(varsinp(2).ne.'lon' ).or.
381
     >     (varsinp(3).ne.'ypos' ).and.(varsinp(3).ne.'lat' ).or.
382
     >     (varsinp(4).ne.'zpos' ).and.(varsinp(4).ne.'depth'   ) )
383
     >then
384
         print*,' ERROR: problem with input trajectories ...'
385
         stop
386
      endif
387
      varsinp(1) = 'time'
388
      varsinp(2) = 'lon'
389
      varsinp(3) = 'lat'
390
      varsinp(4) = 'p'
391
 
392
c     Write some status information of the input trajectories
393
      print*,'---- INPUT TRAJECTORIES ---------------------------------'
394
      print*
395
      print*,' Start date             : ',trim(startdate)
396
      print*,' End date               : ',trim(enddate)
397
      print*,' Reference time (year)  : ',reftime(1)
398
      print*,'                (month) : ',reftime(2)
399
      print*,'                (day)   : ',reftime(3)
400
      print*,'                (hour)  : ',reftime(4)
401
      print*,'                (min)   : ',reftime(5)
402
      print*,' Time range (min)       : ',reftime(6)
403
      do i=1,ncol
404
         print*,' Var                    :',i,trim(varsinp(i))
405
      enddo
406
      print*
407
 
408
c     Check that first time is 0 - otherwise the tracing will produce
409
c     wrong results because later in the code only absolute times are
410
c     considered: <itime0   = int(abs(tfrac-tstart)/timeinc) + 1>. This 
411
c     will be changed in a future version.
412
      if ( abs( trainp(1,1,1) ).gt.eps ) then
413
         print*,' ERROR: First time of trajectory must be 0, i.e. '
414
         print*,'     correspond to the reference date. Otherwise'
415
         print*,'     the tracing will give wrong results... STOP'
416
         stop
417
      endif
418
 
419
c     If requested, open the coordinate dump file
420
      if ( dumpcoord.eq.'yes' ) then
421
         open(10,file=trim(outfile)//'.coord')
422
      endif
423
 
424
c     --------------------------------------------------------------------
425
c     Trace the fields (fields available on input files)
426
c     --------------------------------------------------------------------
427
 
428
      print*
429
      print*,'---- LIDAR FROM PRIMARY AND SECONDARY DATA FILES ------'
430
 
431
c     Loop over all tracing fields
432
      do i=1,ntrace0
433
 
434
c	      Skip all fields marked for online calculation
435
          if ( compfl(i).eq.1 ) goto 110
436
 
437
c	      Init the output fields: position and lidar field
438
	      do k=1,ntim
439
	      	do l=1,npre
440
	      		out_pos(k,l) = 0.
441
	      	    out_val(k,l) = 0.
442
	      	    out_cnt(k,l) = 0.
443
	      	 enddo
444
	      enddo
445
 
446
c         Write some status information
447
          print*
448
          print*,' Now lidaring           : ',
449
     >         trim(tvar(i)),compfl(i),' ',trim(tfil(i))
450
 
451
c         Reset flags for load manager
452
          iloaded0 = -1
453
          iloaded1 = -1
454
 
455
c         Reset the counter for fields outside domain
456
          noutside = 0
457
 
458
c         Loop over all times
459
          do j=1,ntim
460
 
461
c            Convert trajectory time from hh.mm to fractional time
462
             call hhmm2frac(trainp(1,j,1),tfrac)
463
 
464
c            Get the times which are needed
465
             itime0   = int(abs(tfrac-tstart)/timeinc) + 1
466
             time0    = tstart + fbflag * real(itime0-1) * timeinc
467
             itime1   = itime0 + 1
468
             time1    = time0 + fbflag * timeinc
469
             if ( itime1.gt.numdat ) then
470
                itime1 = itime0
471
                time1  = time0
472
             endif
473
 
474
c            Load manager: Check whether itime0 can be copied from itime1
475
             if ( itime0.eq.iloaded1 ) then
476
                f3t0     = f3t1
477
                p3t0     = p3t1
478
                spt0     = spt1
479
                iloaded0 = itime0
480
             endif
481
 
482
c            Load manager: Check whether itime1 can be copied from itime0
483
             if ( itime1.eq.iloaded0 ) then
484
                f3t1     = f3t0
485
                p3t1     = p3t0
486
                spt1     = spt0
487
                iloaded1 = itime1
488
             endif
489
 
490
c            Load manager:  Load first time (tracing variable and grid)
491
             if ( itime0.ne.iloaded0 ) then
492
 
493
                filename = tfil(i)//dat(itime0)
494
                call frac2hhmm(time0,tload)
495
                varname  = tvar(i) 
496
                write(*,'(a23,a20,a3,a5,f7.2)') 
497
     >               '    ->  loading          : ',
498
     >               trim(filename),'  ',trim(varname),tload
499
                call input_open (fid,filename)                
500
                call input_wind 
501
     >               (fid,varname,f3t0,tload,stagz,mdv,
502
     >               xmin,xmax,ymin,ymax,dx,dy,nx,ny,nz,timecheck)             
503
c                call input_grid      
504
c     >               (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,
505
c     >                tload,pollon,pollat,p3t0,spt0,nz,ak,bk,stagz,
506
c     >                timecheck)
507
                call input_close(fid)
508
 
509
                filename = 'P'//dat(itime0)
510
                call input_open (fid,filename)                
511
                varname = 'lev'
512
                call input_grid                                      
513
     >              (fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,
514
     >              0,pollon,pollat,p3t1,spt1,nz,stagz,timecheck)
515
                call input_close(fid)
516
 
517
                iloaded0 = itime0
518
 
519
             endif
520
c            Load manager: Load second time (tracing variable and grid)
521
             if ( itime1.ne.iloaded1 ) then
522
 
523
                filename = tfil(i)//dat(itime1)
524
                call frac2hhmm(time1,tload)
525
                varname  = tvar(i) 
526
                write(*,'(a23,a20,a3,a5,f7.2)') 
527
     >               '    ->  loading          : ',
528
     >               trim(filename),'  ',trim(varname),tload
529
                call input_open (fid,filename)
530
                call input_wind 
531
     >               (fid,varname,f3t1,tload,stagz,mdv,
532
     >               xmin,xmax,ymin,ymax,dx,dy,nx,ny,nz,timecheck)      
533
c                call input_grid      
534
c     >               (-fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,
535
c     >               tload,pollon,pollat,p3t1,spt1,nz,ak,bk,stagz,
536
c     >               timecheck)
537
                call input_close(fid)
538
 
539
                filename = 'P'//dat(itime0)
540
                call input_open (fid,filename)                
541
                varname = 'lev'
542
                call input_grid                                      
543
     >              (fid,varname,xmin,xmax,ymin,ymax,dx,dy,nx,ny,
544
     >              0,pollon,pollat,p3t1,spt1,nz,stagz,timecheck)
545
                call input_close(fid)
546
 
547
                iloaded1 = itime1
548
 
549
             endif
550
 
551
 
552
c            Loop over all trajectories
553
             do k=1,ntra
554
 
555
c               Set the trajectory position 
556
                x0_tra = trainp(k,j,2)                          ! Longitude
557
                y0_tra = trainp(k,j,3)                          ! Latitude
558
                p0_tra = trainp(k,j,4)                          ! Pressure
559
 
560
c               Get rotation angle - orient normal to trajectory
561
                if ( direction.eq.'normal' ) then
562
 
563
                   vx0 = 1.                     
564
                   vy0 = 0.
565
 
566
                   if ( j.lt.ntim ) then
567
                      lat =  0.5 * ( trainp(k,j,3) + trainp(k,j+1,3) )
568
                      vx1 = ( trainp(k,j+1,2) - trainp(k,j,2) ) * 
569
     >                      cos( lat * pi180 )
570
                      vy1 = ( trainp(k,j+1,3) - trainp(k,j,3) )
571
                   else
572
                      lat =  0.5 * ( trainp(k,j,3) + trainp(k,j-1,3) )
573
                      vx1 = ( trainp(k,j,2) - trainp(k,j-1,2) ) * 
574
     >                      cos( lat * pi180 )
575
                      vy1 = ( trainp(k,j,3) - trainp(k,j-1,3) )
576
                   endif
577
 
578
                   if ( vx1.gt.180  ) vx1 = vx1 - 360
579
                   if ( vx1.lt.-180 ) vx1 = vx1 + 360.
580
 
581
                   call getangle (vx0,vy0,vx1,vy1,rotation)
582
                   rotation = -rotation
583
 
584
                else
585
                   rotation = 0.
586
                endif
587
 
588
c               Set the relative time
589
                call hhmm2frac(trainp(k,j,1),tfrac)
590
                reltpos0 = fbflag * (tfrac-time0)/timeinc    
591
 
592
c               Loop over pressure profile (or other positions for horizontal mode)
593
	        do l=1,npre
594
 
595
c                     Vertical
596
                      if ( direction.eq.'vertical' ) then
597
                        x0 = x0_tra
598
                        y0 = y0_tra
599
                        p0 = pmin + real(l-1)/real(npre-1) * (pmax-pmin)
600
                        if ( centering.eq.'yes' )then
601
                           p0 = p0 + trainp(k,j,4)
602
                        endif
603
 
604
c                     Longitude
605
                      elseif ( direction.eq.'lon' ) then
606
                        x0 = pmin + real(l-1)/real(npre-1) * (pmax-pmin)
607
                        y0 = y0_tra
608
                        p0 = p0_tra
609
                        if ( centering.eq.'yes' )then
610
                           x0 = x0 + x0_tra
611
                        endif
612
 
613
c                     Latitude
614
                      elseif ( direction.eq.'lat' ) then
615
                        x0 = x0_tra
616
                        y0 = pmin + real(l-1)/real(npre-1) * (pmax-pmin)
617
                        p0 = p0_tra
618
                        if ( centering.eq.'yes' )then
619
                           y0 = y0 + y0_tra
620
                        endif
621
 
622
c                     Normal to trajerctory
623
                      elseif ( direction.eq.'normal' ) then
624
 
625
c                        Set the coordinate in the rotated system
626
                         rlat = pmin + 
627
     >                             real(l-1)/real(npre-1) * (pmax-pmin)
628
                         rlon = 0.
629
 
630
c                        Transform it back to geographical lon/lat
631
                         call getenvir_b (x0_tra,y0_tra,rotation,
632
     >                                              x0,y0,rlon,rlat,1)
633
 
634
c                        Pressure unchanged
635
                         p0 = p0_tra
636
 
637
                      endif
638
 
639
c                     Handle periodic boundaries in zonal direction
640
                      if ( (x0.gt.xmax).and.(per.ne.0) ) x0 = x0 - 360.
641
                      if ( (x0.lt.xmin).and.(per.ne.0) ) x0 = x0 + 360.
642
 
643
c                     Handle pole problems for hemispheric data (taken from caltra.f)
644
                      if ((hem.eq.1).and.(y0.gt.90.)) then
645
                         y0=180.-y0
646
                         x0=x0+per/2.
647
                      endif
648
                      if ((hem.eq.1).and.(y0.lt.-90.)) then
649
                         y0=-180.-y0
650
                         x0=x0+per/2.
651
                      endif
652
                      if (y0.gt.89.99) then
653
                         y0=89.99
654
                      endif     
655
 
656
c                 If requested, dump the lidar coordinates
657
                  if ( (dumpcoord.eq.'yes').and.(i.eq.1) ) then
658
                     write(10,'(3f10.2)') x0,y0,trainp(k,j,1)
659
                     write(10,'(3f10.2)') x0_tra,y0_tra,5.
660
                  endif
661
 
662
C                 Get the index where to interpolate (x0,y0,p0)
663
                  if ( (abs(x0-mdv).gt.eps).and.
664
     >                 (abs(y0-mdv).gt.eps) )
665
     >            then
666
                     call get_index4 (xind,yind,pind,x0,y0,p0,reltpos0,
667
     >                                p3t0,p3t1,spt0,spt1,3,
668
     >                                nx,ny,nz,xmin,ymin,dx,dy,mdv)
669
                  else
670
                     xind = mdv
671
                     yind = mdv
672
                     pind = mdv
673
                  endif
674
 
675
c                 If requested, apply nearest-neighbor interpolation
676
                  if ( intmode.eq.'nearest') then
677
 
678
                     xind = real( nint(xind) )
679
                     yind = real( nint(yind) )
680
                     pind = real( nint(pind) )
681
 
682
                     if ( xind.lt.1.  ) xind = 1.
683
                     if ( xind.gt.nx  ) xind = real(nx)
684
                     if ( yind.lt.1.  ) yind = 1.
685
                     if ( yind.gt.ny  ) yind = real(ny)
686
 
687
                     if ( pind.lt.1.  ) pind = 1.
688
                     if ( pind.gt.nz  ) pind = real(nz)
689
 
690
                  endif
691
 
692
c                 Do the interpolation: everthing is ok
693
                  if ( (xind.ge.1.).and.(xind.le.real(nx)).and.
694
     >                 (yind.ge.1.).and.(yind.le.real(ny)).and.
695
     >                 (pind.ge.1.).and.(pind.le.real(nz)) )
696
     >            then
697
                     f0 = int_index4(f3t0,f3t1,nx,ny,nz,
698
     >                               xind,yind,pind,reltpos0,mdv)
699
 
700
c                 Set to missing data
701
                  else
702
                     f0       = mdv
703
                  endif
704
 
705
c	              Save result to output array
706
                  if (abs(f0-mdv).gt.eps) then
707
                     out_val(j,l) = out_val(j,l) + f0 * fac(i)
708
                     out_cnt(j,l) = out_cnt(j,l) + 1.
709
 
710
	              endif
711
 
712
c              End loop over all pressure levels
713
	           enddo
714
 
715
c	           Save output - time index
716
	           ind_time = j
717
 
718
c                  Save output - space index for 'no centering'
719
	           if ( centering.eq.'no' ) then
720
                      if ( direction.eq.'vertical') then 
721
                         ind_pre  = nint( real(npre) *
722
     >          	       ( (p0_tra - pmin)/(pmax-pmin) ) + 1.)
723
                      elseif ( direction.eq.'lon') then 
724
                         ind_pre  = nint( real(npre) *
725
     >          	       ( (x0_tra - pmin)/(pmax-pmin) ) + 1.)
726
                      elseif ( direction.eq.'lat') then 
727
                         ind_pre  = nint( real(npre) *
728
     >          	       ( (y0_tra - pmin)/(pmax-pmin) ) + 1.)
729
                      endif
730
 
731
c                  Save output - space index for 'centering'
732
	           else
733
	           	  ind_pre  = nint( real(npre) *
734
     >          	       ( (0.            - pmin)/(pmax-pmin) ) + 1.)
735
	           endif
736
 
737
c                  Update the output array
738
	           if ( (ind_time.ge.1).and.(ind_time.le.ntim).and.
739
     >              (ind_pre .ge.1).and.(ind_pre .le.npre) )
740
     >         then
741
                    out_pos(ind_time,ind_pre) =
742
     >                          	out_pos(ind_time,ind_pre) + 1.
743
	           endif
744
 
745
c	         End loop over all trajectories
746
             enddo
747
 
748
c	      End loop over all times
749
          enddo
750
 
751
c	      Write the trajectory position to netCDF file - only once
752
	      if ( i.eq.1 ) then
753
	      	  cdfname  = outfile
754
	      	  varname  = 'POSITION'
755
	      	  longname = 'position of trajectory points'
756
	      	  unit     = 'none'
757
	      	  time     = 0.
758
              do k=1,npre
759
              	levels(k) = pmin + real(k-1)/real(npre-1) * (pmax-pmin)
760
              enddo
761
              do k=1,ntim
762
                 times(k) = trainp(1,k,1)
763
              enddo
764
              call writecdf2D_cf
765
     >            (cdfname,varname,longname,unit,out_pos,time,levels,
766
     >             times,npre,ntim,1,1,direction)
767
	      endif
768
 
769
c	      If no valid lidar count: set the field to missing data
770
          do k=1,ntim
771
          	do l=1,npre
772
          		if (abs(out_cnt(k,l)).lt.eps) then
773
          			out_val(k,l) = mdv
774
          	    endif
775
          	 enddo
776
          enddo
777
 
778
c	      If requested, calculate the mean of the lidar field
779
	      if ( outmode.eq.'mean' ) then
780
	      	do k=1,ntim
781
	      		do l=1,npre
782
	      			if ( (abs(out_val(k,l)-mdv).gt.eps).and.
783
     >                   (abs(out_cnt(k,l)    ).gt.0. ) )
784
     >              then
785
	      				out_val(k,l) = out_val(k,l) / out_cnt(k,l)
786
	      		    endif
787
	      		 enddo
788
	          enddo
789
	      endif
790
 
791
c	      Write the lidar field and count
792
	      cdfname  = outfile
793
	      if (outmode.eq.'sum' ) then
794
	         varname  = trim(tvar(i))//'_SUM'
795
	      elseif (outmode.eq.'mean' ) then
796
	         varname  = trim(tvar(i))//'_MEAN'
797
	      endif
798
	      longname = 'sum over all '//trim(tvar(i))//' profiles'
799
	      unit     = 'not given'
800
	      time     = 0.
801
          call writecdf2D_cf
802
     >            (cdfname,varname,longname,unit,out_val,time,levels,
803
     >             times,npre,ntim,0,1,direction)
804
 
805
	  	  cdfname  = outfile
806
	      varname  = trim(tvar(i))//'_CNT'
807
	      longname = 'counts of all '//trim(tvar(i))//' profiles'
808
	      unit     = 'not given'
809
	      time     = 0.
810
          call writecdf2D_cf
811
     >            (cdfname,varname,longname,unit,out_cnt,time,levels,
812
     >             times,npre,ntim,0,1,direction)
813
 
814
c         Exit point for loop over all tracing variables
815
 110      continue
816
 
817
c	   End loop over all lidar variables
818
       enddo
819
 
820
 
821
c     --------------------------------------------------------------------
822
c     Write output to netCDF file
823
c     --------------------------------------------------------------------
824
 
825
c     Write status information
826
      print*
827
      print*,'---- WRITE OUTPUT LIDAR FIELDS --------------------------'
828
      print*
829
 
830
c     Close coord dump file
831
      print*,' LIDAR written to      : ',trim(outfile)
832
      if ( dumpcoord.eq.'yes' ) then
833
        print*,' Coordinates dumped to : ',trim(outfile)//'.coord'
834
      endif
835
 
836
c     Write some status information, and end of program message
837
      print*  
838
      print*,'---- STATUS INFORMATION --------------------------------'
839
      print*
840
      print*,' ok'
841
      print*
842
      print*,'              *** END OF PROGRAM LIDAR ***'
843
      print*,'========================================================='
844
 
845
 
846
      end 
847
 
848
 
849
c     ********************************************************************
850
c     * INPUT / OUTPUT SUBROUTINES                                       *
851
c     ********************************************************************
852
 
853
c     --------------------------------------------------------------------
854
c     Subroutines to write 2D CF netcdf output file
855
c     --------------------------------------------------------------------
856
 
857
      subroutine writecdf2D_cf
858
     >          (cdfname,varname,longname,unit,arr,time,levels,times,
859
     >           npre,ntim,crefile,crevar,direction)
860
 
861
c     Create and write to the CF netcdf file <cdfname>. The variable
862
c     with name <varname> and with time <time> is written. The data
863
c     are in the two-dimensional array <arr>.  The flags <crefile> and
864
c     <crevar> determine whether the file and/or the variable should
865
c     be created.
866
 
867
      USE netcdf
868
 
869
      IMPLICIT NONE
870
 
871
c     Declaration of input parameters
872
      character*80 cdfname
873
      character*80 varname,longname,unit
874
      integer      npre,ntim
875
      real         arr(ntim,npre)
876
      real         levels(npre)
877
      real         times (ntim)
878
      real         time
879
      integer      crefile,crevar
880
      character*80 direction
881
 
882
c     Numerical epsilon
883
      real         eps
884
      parameter    (eps=1.e-5)
885
 
886
c     Local variables
887
      integer      ierr
888
      integer      ncID
889
      integer      LevDimId,    varLevID
890
      integer      TimeDimID,   varTimeID
891
      real         timeindex
892
      integer      i,j
893
      integer      nvars,varids(100)
894
      integer      ndims,dimids(100)
895
      real         timelist(1000)
896
      integer      ntimes
897
      integer      ind
898
      integer      varID
899
 
900
c     Quick an dirty solution for fieldname conflict
901
      if ( varname.eq.'time' ) varname = 'TIME'
902
 
903
c     Initially set error to indicate no errors.
904
      ierr = 0
905
 
906
c     ---- Create the netCDF - skip if <crefile=0> ----------------------
907
      if ( crefile.ne.1 ) goto 100
908
 
909
c     Create the file
910
      ierr = nf90_create(trim(cdfname), NF90_CLOBBER, ncID)
911
 
912
c     Define dimensions
913
      ierr=nf90_def_dim(ncID,'level',npre, LevDimID )
914
      ierr=nf90_def_dim(ncID,'time' ,ntim, TimeDimID)
915
 
916
c     Define space coordinate 
917
      ierr = nf90_def_var(ncID,'level',NF90_FLOAT,
918
     >     (/ LevDimID /),varLevID)
919
      if ( direction.eq.'vertical' ) then
920
        ierr = nf90_put_att(ncID, varLevID, "standard_name","level")
921
        ierr = nf90_put_att(ncID, varLevID, "units"        ,"m")
922
      elseif ( direction.eq.'lat' ) then
923
        ierr = nf90_put_att(ncID, varLevID, "standard_name","latitude")
924
        ierr = nf90_put_att(ncID, varLevID, "units"        ,"deg")
925
      elseif ( direction.eq.'lon' ) then
926
        ierr = nf90_put_att(ncID, varLevID, "standard_name","longitude")
927
        ierr = nf90_put_att(ncID, varLevID, "units"        ,"deg")
928
      elseif ( direction.eq.'normal' ) then
929
        ierr = nf90_put_att(ncID, varLevID, "standard_name","normal")
930
        ierr = nf90_put_att(ncID, varLevID, "units"        ,"deg")
931
      endif
932
 
933
c     Define time coordinate
934
      ierr = nf90_def_var(ncID,'time',NF90_FLOAT,
935
     >     (/ TimeDimID /), varTimeID)
936
      ierr = nf90_put_att(ncID, varTimeID, "long_name",    "time")
937
      ierr = nf90_put_att(ncID, varTimeID, "units",       "hours")
938
 
939
c     Write global attributes
940
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'Conventions', 'CF-1.0')
941
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'title',
942
     >     'pseudo-lidar from trajectory file')
943
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'source',
944
     >     'Lagranto Trajectories')
945
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'institution',
946
     >     'ETH Zurich, IACETH')
947
 
948
c     Check whether the definition was successful
949
      ierr = nf90_enddef(ncID)
950
      if (ierr.gt.0) then
951
         print*, 'An error occurred while attempting to ',
952
     >        'finish definition mode.'
953
         stop
954
      endif
955
 
956
c     Write coordinate data
957
      ierr = nf90_put_var(ncID,varLevID  ,levels)
958
      ierr = nf90_put_var(ncID,varTimeID ,times )
959
 
960
c     Close netCDF file
961
      ierr = nf90_close(ncID)
962
 
963
 100  continue
964
 
965
c     ---- Define a new variable - skip if <crevar=0> -----------------------
966
 
967
      if ( crevar.ne.1 ) goto 110
968
 
969
      print*,'Now defining ',trim(varname)
970
 
971
c     Open the file for read/write access
972
      ierr = nf90_open  (trim(cdfname), NF90_WRITE  , ncID)
973
 
974
c     Get the IDs for dimensions
975
      ierr = nf90_inq_dimid(ncID,'level', LevDimID )
976
      ierr = nf90_inq_dimid(ncID,'time' , TimeDimID)
977
 
978
c     Enter define mode
979
      ierr = nf90_redef(ncID)
980
 
981
c     Write definition and add attributes
982
      ierr = nf90_def_var(ncID,varname,NF90_FLOAT,
983
     >                   (/ TimeDimID, LevDimID /),varID)
984
      ierr = nf90_put_att(ncID, varID, "long_name" , longname )
985
      ierr = nf90_put_att(ncID, varID, "units"     , unit     )
986
      ierr = nf90_put_att(ncID, varID, '_FillValue', -999.99  )
987
 
988
c     Check whether definition was successful
989
      ierr = nf90_enddef(ncID)
990
      if (ierr.gt.0) then
991
         print*, 'An error occurred while attempting to ',
992
     >           'finish definition mode.'
993
         stop
994
      endif
995
 
996
c     Close netCDF file
997
      ierr = nf90_close(ncID)
998
 
999
 110  continue
1000
 
1001
c     ---- Write data --------------------------------------------------
1002
 
1003
c     Open the file for read/write access
1004
      ierr = nf90_open  (trim(cdfname), NF90_WRITE , ncID)
1005
 
1006
c     Get the varID
1007
      ierr = nf90_inq_varid(ncID,varname, varID )
1008
      if (ierr.ne.0) then
1009
         print*,'Variable ',trim(varname),' is not defined on ',
1010
     >          trim(cdfname)
1011
         stop
1012
      endif
1013
 
1014
c     Write data block
1015
      ierr = nf90_put_var(ncID,varID,arr,
1016
     >                    start = (/ 1, 1 /),
1017
     >                    count = (/ ntim, npre/) )
1018
 
1019
c     Check whether writing was successful
1020
      ierr = nf90_close(ncID)
1021
      if (ierr.ne.0) then
1022
         write(*,*) trim(nf90_strerror(ierr))
1023
         write(*,*) 'An error occurred while attempting to ',
1024
     >              'close the netcdf file.'
1025
         write(*,*) 'in clscdf_CF'
1026
      endif
1027
 
1028
      end
1029
 
1030
c     ********************************************************************************
1031
c     * Coordinate rotation - lidar normal to trajectory                             *
1032
c     ********************************************************************************
1033
 
1034
c     --------------------------------------------------------------------------------
1035
c     Backward coordinate transformation (Rotated lon/lat -> True lon/lat)
1036
c     --------------------------------------------------------------------------------
1037
 
1038
      SUBROUTINE getenvir_b (clon,clat,rotation,
1039
     >                       lon,lat,rlon,rlat,n)
1040
 
1041
      implicit none
1042
 
1043
c     Declaration of input and output parameters
1044
      integer     n
1045
      real        clon,clat,rotation
1046
      real        lon(n), lat(n)
1047
      real        rlon(n),rlat(n)
1048
 
1049
c     Auxiliary variables 
1050
      real         pollon,pollat
1051
      integer      i
1052
      real         rlon1(n),rlat1(n)
1053
 
1054
c     Externals
1055
      real         lmstolm,phstoph
1056
      external     lmstolm,phstoph
1057
 
1058
c     First coordinate transformation (make the local coordinate system parallel to equator)
1059
      pollon=-180.
1060
      pollat=90.+rotation
1061
      do i=1,n
1062
         rlon1(i)=90.+lmstolm(rlat(i),rlon(i)-90.,pollat,pollon)
1063
         rlat1(i)=phstoph(rlat(i),rlon(i)-90.,pollat,pollon)            
1064
      enddo
1065
 
1066
c     Second coordinate transformation (make the local coordinate system parallel to equator)
1067
      pollon=clon-180.
1068
      if (pollon.lt.-180.) pollon=pollon+360.
1069
      pollat=90.-clat
1070
      do i=1,n
1071
         lon(i)=lmstolm(rlat1(i),rlon1(i),pollat,pollon)
1072
         lat(i)=phstoph(rlat1(i),rlon1(i),pollat,pollon)            
1073
      enddo
1074
 
1075
      END
1076
 
1077
c     ---------------------------------------------------------------------
1078
c     Determine the angle between two vectors
1079
c     ---------------------------------------------------------------------
1080
 
1081
      SUBROUTINE getangle (vx1,vy1,vx2,vy2,angle)
1082
 
1083
c     Given two vectors <vx1,vy1> and <vx2,vy2>, determine the angle (in deg) 
1084
c     between the two vectors.
1085
 
1086
      implicit none
1087
 
1088
c     Declaration of subroutine parameters
1089
      real vx1,vy1
1090
      real vx2,vy2
1091
      real angle
1092
 
1093
c     Auxiliary variables and parameters
1094
      real len1,len2,len3
1095
      real val1,val2,val3
1096
      real pi
1097
      parameter (pi=3.14159265359)
1098
 
1099
      len1=sqrt(vx1*vx1+vy1*vy1)
1100
      len2=sqrt(vx2*vx2+vy2*vy2)
1101
 
1102
      if ((len1.gt.0.).and.(len2.gt.0.)) then
1103
         vx1=vx1/len1
1104
         vy1=vy1/len1
1105
         vx2=vx2/len2
1106
         vy2=vy2/len2
1107
 
1108
         val1=vx1*vx2+vy1*vy2
1109
         val2=-vy1*vx2+vx1*vy2
1110
 
1111
         len3=sqrt(val1*val1+val2*val2)
1112
 
1113
         if ( (val1.ge.0.).and.(val2.ge.0.) ) then
1114
            val3=acos(val1/len3)
1115
         else if ( (val1.lt.0.).and.(val2.ge.0.) ) then
1116
            val3=pi-acos(abs(val1)/len3)
1117
         else if ( (val1.ge.0.).and.(val2.le.0.) ) then
1118
            val3=-acos(val1/len3)
1119
         else if ( (val1.lt.0.).and.(val2.le.0.) ) then
1120
            val3=-pi+acos(abs(val1)/len3)
1121
         endif
1122
      else
1123
         val3=0.
1124
      endif
1125
 
1126
      angle=180./pi*val3                                                                                     
1127
 
1128
      END
1129
 
1130
c     --------------------------------------------------------------------------------
1131
c     Transformation routine: LMSTOLM and PHSTOPH from library gm2em            
1132
c     --------------------------------------------------------------------------------
1133
 
1134
      REAL FUNCTION LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1135
C
1136
C**** LMSTOLM  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1137
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1138
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1139
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1140
C**   AUFRUF   :   LAM = LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1141
C**   ENTRIES  :   KEINE
1142
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1143
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1144
C**                IM ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1145
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1146
C**   VERSIONS-
1147
C**   DATUM    :   03.05.90
1148
C**
1149
C**   EXTERNALS:   KEINE
1150
C**   EINGABE-
1151
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1152
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1153
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1154
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1155
C**   AUSGABE-
1156
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1157
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1158
C**
1159
C**   COMMON-
1160
C**   BLOECKE  :   KEINE
1161
C**
1162
C**   FEHLERBE-
1163
C**   HANDLUNG :   KEINE
1164
C**   VERFASSER:   D.MAJEWSKI
1165
 
1166
      REAL        LAMS,PHIS,POLPHI,POLLAM
1167
 
1168
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1169
 
1170
      ZSINPOL = SIN(ZPIR18*POLPHI)
1171
      ZCOSPOL = COS(ZPIR18*POLPHI)
1172
      ZLAMPOL = ZPIR18*POLLAM
1173
      ZPHIS   = ZPIR18*PHIS
1174
      ZLAMS   = LAMS
1175
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1176
      ZLAMS   = ZPIR18*ZLAMS
1177
 
1178
      ZARG1   = SIN(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1179
     1                          ZCOSPOL*           SIN(ZPHIS)) -
1180
     2          COS(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1181
      ZARG2   = COS(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1182
     1                          ZCOSPOL*           SIN(ZPHIS)) +
1183
     2          SIN(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1184
      IF (ABS(ZARG2).LT.1.E-30) THEN
1185
        IF (ABS(ZARG1).LT.1.E-30) THEN
1186
          LMSTOLM =   0.0
1187
        ELSEIF (ZARG1.GT.0.) THEN
1188
              LMSTOLAM =  90.0
1189
            ELSE
1190
              LMSTOLAM = -90.0
1191
            ENDIF
1192
      ELSE
1193
        LMSTOLM = ZRPI18*ATAN2(ZARG1,ZARG2)
1194
      ENDIF
1195
 
1196
      RETURN
1197
      END
1198
 
1199
 
1200
      REAL FUNCTION PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1201
C
1202
C**** PHSTOPH  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1203
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1204
C****                 ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1205
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1206
C**   AUFRUF   :   PHI = PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1207
C**   ENTRIES  :   KEINE
1208
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1209
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1210
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1211
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1212
C**   VERSIONS-
1213
C**   DATUM    :   03.05.90
1214
C**
1215
C**   EXTERNALS:   KEINE
1216
C**   EINGABE-
1217
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1218
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1219
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1220
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1221
C**   AUSGABE-
1222
C**   PARAMETER:   WAHRE GEOGRAPHISCHE BREITE ALS WERT DER FUNKTION
1223
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1224
C**
1225
C**   COMMON-
1226
C**   BLOECKE  :   KEINE
1227
C**
1228
C**   FEHLERBE-
1229
C**   HANDLUNG :   KEINE
1230
C**   VERFASSER:   D.MAJEWSKI
1231
 
1232
      REAL        LAMS,PHIS,POLPHI,POLLAM
1233
 
1234
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1235
 
1236
      SINPOL = SIN(ZPIR18*POLPHI)
1237
      COSPOL = COS(ZPIR18*POLPHI)
1238
      ZPHIS  = ZPIR18*PHIS
1239
      ZLAMS  = LAMS
1240
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1241
      ZLAMS  = ZPIR18*ZLAMS
1242
      ARG     = COSPOL*COS(ZPHIS)*COS(ZLAMS) + SINPOL*SIN(ZPHIS)
1243
 
1244
      PHSTOPH = ZRPI18*ASIN(ARG)
1245
 
1246
      RETURN
1247
      END
1248
 
1249
 
1250
      REAL FUNCTION LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1251
C
1252
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1253
C
1254
C**** LMTOLMS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM
1255
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1256
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1257
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1258
C**   AUFRUF   :   LAM = LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1259
C**   ENTRIES  :   KEINE
1260
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM AUF
1261
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1262
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1263
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1264
C**   VERSIONS-
1265
C**   DATUM    :   03.05.90
1266
C**
1267
C**   EXTERNALS:   KEINE
1268
C**   EINGABE-
1269
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1270
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1271
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1272
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1273
C**   AUSGABE-
1274
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1275
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1276
C**
1277
C**   COMMON-
1278
C**   BLOECKE  :   KEINE
1279
C**
1280
C**   FEHLERBE-
1281
C**   HANDLUNG :   KEINE
1282
C**   VERFASSER:   G. DE MORSIER
1283
 
1284
      REAL        LAM,PHI,POLPHI,POLLAM
1285
 
1286
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1287
 
1288
      ZSINPOL = SIN(ZPIR18*POLPHI)
1289
      ZCOSPOL = COS(ZPIR18*POLPHI)
1290
      ZLAMPOL =     ZPIR18*POLLAM
1291
      ZPHI    =     ZPIR18*PHI
1292
      ZLAM    = LAM
1293
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1294
      ZLAM    = ZPIR18*ZLAM
1295
 
1296
      ZARG1   = - SIN(ZLAM-ZLAMPOL)*COS(ZPHI)
1297
      ZARG2   = - ZSINPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL)+ZCOSPOL*SIN(ZPHI)
1298
      IF (ABS(ZARG2).LT.1.E-30) THEN
1299
        IF (ABS(ZARG1).LT.1.E-30) THEN
1300
          LMTOLMS =   0.0
1301
        ELSEIF (ZARG1.GT.0.) THEN
1302
              LMTOLMS =  90.0
1303
            ELSE
1304
              LMTOLMS = -90.0
1305
            ENDIF
1306
      ELSE
1307
        LMTOLMS = ZRPI18*ATAN2(ZARG1,ZARG2)
1308
      ENDIF
1309
 
1310
      RETURN
1311
      END
1312
 
1313
 
1314
      REAL FUNCTION PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1315
C
1316
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1317
C
1318
C**** PHTOPHS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI
1319
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1320
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1321
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1322
C**   AUFRUF   :   PHI = PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1323
C**   ENTRIES  :   KEINE
1324
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI AUF
1325
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1326
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1327
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1328
C**   VERSIONS-
1329
C**   DATUM    :   03.05.90
1330
C**
1331
C**   EXTERNALS:   KEINE
1332
C**   EINGABE-
1333
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1334
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1335
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1336
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1337
C**   AUSGABE-
1338
C**   PARAMETER:   ROTIERTE BREITE PHIS ALS WERT DER FUNKTION
1339
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1340
C**
1341
C**   COMMON-
1342
C**   BLOECKE  :   KEINE
1343
C**
1344
C**   FEHLERBE-
1345
C**   HANDLUNG :   KEINE
1346
C**   VERFASSER:   G. DE MORSIER
1347
 
1348
      REAL        LAM,PHI,POLPHI,POLLAM
1349
 
1350
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1351
 
1352
      ZSINPOL = SIN(ZPIR18*POLPHI)
1353
      ZCOSPOL = COS(ZPIR18*POLPHI)
1354
      ZLAMPOL = ZPIR18*POLLAM
1355
      ZPHI    = ZPIR18*PHI
1356
      ZLAM    = LAM
1357
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1358
      ZLAM    = ZPIR18*ZLAM
1359
      ZARG    = ZCOSPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL) + ZSINPOL*SIN(ZPHI)
1360
 
1361
      PHTOPHS = ZRPI18*ASIN(ZARG)
1362
 
1363
      RETURN
1364
      END
1365