Subversion Repositories lagranto.ecmwf

Rev

Rev 13 | Rev 29 | Go to most recent revision | Only display areas with differences | Ignore whitespace | Details | Blame | Last modification | View Log | RSS feed

Rev 13 Rev 15
1
      PROGRAM density
1
      PROGRAM density
2
 
2
 
3
      use netcdf
3
      use netcdf
4
 
4
 
5
      implicit none
5
      implicit none
6
 
6
 
7
c     ---------------------------------------------------------------------
7
c     ---------------------------------------------------------------------
8
c     Declaration of variables
8
c     Declaration of variables
9
c     ---------------------------------------------------------------------
9
c     ---------------------------------------------------------------------
10
      
10
      
11
c     Parameter and working arrays
11
c     Parameter and working arrays
12
      real                                    radius
12
      real                                    radius
13
      character*80                            runit
13
      character*80                            runit
14
      integer                                 nx,ny
14
      integer                                 nx,ny
15
      integer                                 nlonlat
15
      integer                                 nlonlat
16
      real                                    dlonlat
16
      real                                    dlonlat
17
      real                                    xmin,ymin,dx,dy
17
      real                                    xmin,ymin,dx,dy
18
      real                                    clon,clat
18
      real                                    clon,clat
19
      integer                                 ntime,nfield,ntra
19
      integer                                 ntime,nfield,ntra
20
      character*80                            inpfile
20
      character*80                            inpfile
21
      character*80                            outfile
21
      character*80                            outfile
22
      character*80                            mode
22
      character*80                            mode
23
      real                                    param
23
      real                                    param
24
      integer                                 opts,npts
24
      integer                                 opts,npts
25
      integer                                 step
25
      integer                                 step
26
      character*80                            gridtype
26
      character*80                            gridtype
27
      character*80                            field
27
      character*80                            field
28
      integer                                 crefile,crevar
28
      integer                                 crefile,crevar
29
      real,allocatable,    dimension (:,:) :: cnt,res,fld,area
29
      real,allocatable,    dimension (:,:) :: cnt,res,fld,area
30
      real,allocatable,    dimension (:)   :: traj
30
      real,allocatable,    dimension (:)   :: traj
31
      real,allocatable,    dimension (:)   :: olon,olat,otim,ofld
31
      real,allocatable,    dimension (:)   :: olon,olat,otim,ofld
32
      real,allocatable,    dimension (:)   :: nlon,nlat,ntim,nfld
32
      real,allocatable,    dimension (:)   :: nlon,nlat,ntim,nfld
33
 
33
 
34
c     Output format
34
c     Output format
35
      character*80                            outformat
35
      character*80                            outformat
36
 
36
 
37
c     Physical and mathematical constants
37
c     Physical and mathematical constants
38
      real                                    pi180
38
      real                                    pi180
39
      parameter                               (pi180=3.14159/180.)
39
      parameter                               (pi180=3.14159/180.)
40
      real                                    deltay
40
      real                                    deltay
41
      parameter                               (deltay=111.)
41
      parameter                               (deltay=111.)
42
      real                                    eps
42
      real                                    eps
43
      parameter                               (eps=0.001)
43
      parameter                               (eps=0.001)
44
 
44
 
45
c     Input trajectories (see iotra.f)
45
c     Input trajectories (see iotra.f)
46
      integer                                 inpmode
46
      integer                                 inpmode
47
      real,allocatable, dimension (:,:,:) ::  trainp     
47
      real,allocatable, dimension (:,:,:) ::  trainp     
48
      integer                                 reftime(6)      
48
      integer                                 reftime(6)      
49
      character*80                            varsinp(100)   
49
      character*80                            varsinp(100)   
50
      integer,allocatable, dimension (:) ::   sel_flag
50
      integer,allocatable, dimension (:) ::   sel_flag
51
      character*80                            sel_file
51
      character*80                            sel_file
52
      character*80                            sel_format
52
      character*80                            sel_format
53
 
53
 
54
c     Auxiliary variables
54
c     Auxiliary variables
55
      character*80                            cdfname,varname
55
      character*80                            cdfname,varname
56
      integer                                 i,j,k
56
      integer                                 i,j,k
57
      integer                                 stat
57
      integer                                 stat
58
      integer,allocatable, dimension (:,:) :: connect0
58
      integer,allocatable, dimension (:,:) :: connect0
59
      integer                                 connectval0
59
      integer                                 connectval0
60
      integer,allocatable, dimension (:,:) :: connect1
60
      integer,allocatable, dimension (:,:) :: connect1
61
      integer                                 connectval1
61
      integer                                 connectval1
62
      integer,allocatable, dimension (:,:) :: connect2
62
      integer,allocatable, dimension (:,:) :: connect2
63
      integer                                 connectval2
63
      integer                                 connectval2
64
      real                                    slat
64
      real                                    slat
65
      integer                                 ipre
65
      integer                                 ipre
66
      real                                    addvalue
66
      real                                    addvalue
67
      real                                    xmax,ymax
67
      real                                    xmax,ymax
68
      real ,allocatable, dimension (:)  ::    odist,ndist
68
      real ,allocatable, dimension (:)  ::    odist,ndist
69
      real                                    dt
69
      real                                    dt
70
      integer                                 fid
70
      integer                                 fid
71
      integer                                 dynamic_grid
71
      integer                                 dynamic_grid
72
      real                                    ycen,xcen
72
      real                                    ycen,xcen
73
      integer                                 indx,indy
73
      integer                                 indx,indy
74
      character*80                            unit
74
      character*80                            unit
75
      real                                    pollon,pollat
75
      real                                    pollon,pollat
76
      real                                    rlon0,rlat0,rlon,rlat
76
      real                                    rlon0,rlat0,rlon,rlat
77
      real                                    lon,lat
77
      real                                    lon,lat
78
      real                                    crot
78
      real                                    crot
79
      integer                                 count
79
      integer                                 count
80
      character*80                            longname, varunit
80
      character*80                            longname, varunit
81
      real                                    time
81
      real                                    time
82
      integer                                 ind
82
      integer                                 ind
83
      integer                                 ifield
83
      integer                                 ifield
84
      real                                    hhmm,frac
84
      real                                    hhmm,frac
85
      integer                                 ierr,ncID
85
      integer                                 ierr,ncID
86
 
86
 
87
c     External functions
87
c     External functions
88
      real         lmstolm,lmtolms
88
      real         lmstolm,lmtolms
89
      real         phstoph,phtophs
89
      real         phstoph,phtophs
90
      external     lmstolm,lmtolms,phstoph,phtophs
90
      external     lmstolm,lmtolms,phstoph,phtophs
91
      
91
      
92
      real         sdis
92
      real         sdis
93
      external     sdis
93
      external     sdis
94
 
94
 
95
c     ---------------------------------------------------------------------
95
c     ---------------------------------------------------------------------
96
c     Preparations
96
c     Preparations
97
c     ---------------------------------------------------------------------
97
c     ---------------------------------------------------------------------
98
 
98
 
99
c     Write start message
99
c     Write start message
100
      print*,'========================================================='
100
      print*,'========================================================='
101
      print*,'              *** START OF PROGRAM DENSITY ***'
101
      print*,'              *** START OF PROGRAM DENSITY ***'
102
      print*
102
      print*
103
 
103
 
104
c     Read input parameters
104
c     Read input parameters
105
      open(10,file='density.param')
105
      open(10,file='density.param')
106
       read(10,*) inpfile
106
       read(10,*) inpfile
107
       read(10,*) outfile
107
       read(10,*) outfile
108
       read(10,*) field
108
       read(10,*) field
109
       read(10,*) ntime,nfield,ntra
109
       read(10,*) ntime,nfield,ntra
110
       read(10,*) gridtype
110
       read(10,*) gridtype
111
       if ( gridtype.eq.'latlon' ) then 
111
       if ( gridtype.eq.'latlon' ) then 
112
          read(10,*) nx,ny,xmin,ymin,dx,dy
112
          read(10,*) nx,ny,xmin,ymin,dx,dy
113
       elseif ( gridtype.eq.'rotated') then
113
       elseif ( gridtype.eq.'rotated') then
114
          read(10,*) clon,clat,nlonlat,dlonlat
114
          read(10,*) clon,clat,nlonlat,dlonlat
115
       else
115
       else
116
          print*,' ERROR: unsupported grid type ',trim(gridtype)
116
          print*,' ERROR: unsupported grid type ',trim(gridtype)
117
          stop
117
          stop
118
       endif
118
       endif
119
       read(10,*) radius,runit
119
       read(10,*) radius,runit
120
       read(10,*) mode
120
       read(10,*) mode
121
       read(10,*) param
121
       read(10,*) param
122
       read(10,*) step
122
       read(10,*) step
123
       read(10,*) sel_file
123
       read(10,*) sel_file
124
       read(10,*) sel_format
124
       read(10,*) sel_format
125
       read(10,*) crefile
125
       read(10,*) crefile
126
       read(10,*) crevar
126
       read(10,*) crevar
127
      close(10)
127
      close(10)
128
 
128
 
129
c     Get the grid parameters if <crefile=0>
129
c     Get the grid parameters if <crefile=0>
130
      if ( crefile.eq.0 ) then
130
      if ( crefile.eq.0 ) then
131
 
131
 
132
           ierr = nf90_open  (trim(outfile), NF90_NOWRITE  , ncID)
132
           ierr = nf90_open  (trim(outfile), NF90_NOWRITE  , ncID)
133
 
133
 
134
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'grid'   ,gridtype ) 
134
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'grid'   ,gridtype ) 
135
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'clon'   ,clon     )
135
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'clon'   ,clon     )
136
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'clat'   ,clat     )
136
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'clat'   ,clat     )
137
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'nlonlat',nlonlat  )
137
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'nlonlat',nlonlat  )
138
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dlonlat',dlonlat  )
138
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dlonlat',dlonlat  )
139
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'nx'     ,nx       )
139
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'nx'     ,nx       )
140
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'ny'     ,ny       )
140
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'ny'     ,ny       )
141
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dx'     ,dx       )
141
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dx'     ,dx       )
142
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dy'     ,dy       )
142
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'dy'     ,dy       )
143
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'xmin'   ,xmin     )
143
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'xmin'   ,xmin     )
144
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'ymin'   ,ymin     )
144
           ierr = nf90_get_att(ncID, NF90_GLOBAL, 'ymin'   ,ymin     )
145
 
145
 
146
           ierr = nf90_close(ncID)
146
           ierr = nf90_close(ncID)
147
 
147
 
148
           print*,'**** GRID PARAMETERS IMPORTED ',
148
           print*,'**** GRID PARAMETERS IMPORTED ',
149
     >            'FROM NETCDF FILE!!!! ****'
149
     >            'FROM NETCDF FILE!!!! ****'
150
           print*
150
           print*
151
           
151
           
152
      endif
152
      endif
153
 
153
 
154
c     Check for consistency
154
c     Check for consistency
155
      if ( (step.ne.0).and.(mode.ne.'keep') ) then
155
      if ( (step.ne.0).and.(mode.ne.'keep') ) then
156
         print*," ERROR: interpolation is only possible for all",
156
         print*," ERROR: interpolation is only possible for all",
157
     >                   ' time steps... Stop'
157
     >                   ' time steps... Stop'
158
         stop
158
         stop
159
      endif
159
      endif
160
 
160
 
161
c     Set the number of times (just code aesthetics)
161
c     Set the number of times (just code aesthetics)
162
      opts=ntime
162
      opts=ntime
163
 
163
 
164
c     Set grid parameters for rotated grid
164
c     Set grid parameters for rotated grid
165
      if ( gridtype.eq.'rotated' ) then
165
      if ( gridtype.eq.'rotated' ) then
166
         nx   = nlonlat
166
         nx   = nlonlat
167
         ny   = nlonlat
167
         ny   = nlonlat
168
         dx   = dlonlat
168
         dx   = dlonlat
169
         dy   = dlonlat
169
         dy   = dlonlat
170
         xmin = - real(nlonlat-1)/2. * dx
170
         xmin = - real(nlonlat-1)/2. * dx
171
         xmax = + real(nlonlat-1)/2. * dx
171
         xmax = + real(nlonlat-1)/2. * dx
172
         ymin = - real(nlonlat-1)/2. * dy
172
         ymin = - real(nlonlat-1)/2. * dy
173
         ymax = + real(nlonlat-1)/2. * dy
173
         ymax = + real(nlonlat-1)/2. * dy
174
      endif
174
      endif
175
      
175
      
176
c     Set the flag for dynamic grid adjustment
176
c     Set the flag for dynamic grid adjustment
177
      if ( (nx.eq.0).or.(ny.eq.0) ) then
177
      if ( (nx.eq.0).or.(ny.eq.0) ) then
178
         dynamic_grid = 1
178
         dynamic_grid = 1
179
      else
179
      else
180
         dynamic_grid = 0
180
         dynamic_grid = 0
181
      endif
181
      endif
182
 
182
 
183
c     Print status information
183
c     Print status information
184
      print*,'---- INPUT PARAMETERS -----------------------------------'
184
      print*,'---- INPUT PARAMETERS -----------------------------------'
185
      print* 
185
      print* 
186
      print*,'Input                : ',trim(inpfile)
186
      print*,'Input                : ',trim(inpfile)
187
      print*,'Output               : ',trim(outfile)
187
      print*,'Output               : ',trim(outfile)
188
      print*,'Field                : ',trim(field)
188
      print*,'Field                : ',trim(field)
189
      print*,'Trajectory           : ',ntime,nfield,ntra
189
      print*,'Trajectory           : ',ntime,nfield,ntra
190
      print*,'Grid type            : ',trim(gridtype)
190
      print*,'Grid type            : ',trim(gridtype)
191
      if ( dynamic_grid.eq.1 ) then
191
      if ( dynamic_grid.eq.1 ) then
192
         print*,'Grid                 : dynamic (see below)'
192
         print*,'Grid                 : dynamic (see below)'
193
      elseif ( gridtype.eq.'latlon' ) then
193
      elseif ( gridtype.eq.'latlon' ) then
194
         print*,'Grid   nlon,nlat     : ',nx,ny
194
         print*,'Grid   nlon,nlat     : ',nx,ny
195
         print*,'       lonmin,latmin : ',xmin,ymin
195
         print*,'       lonmin,latmin : ',xmin,ymin
196
         print*,'       dlon,dlat     : ',dx,dy
196
         print*,'       dlon,dlat     : ',dx,dy
197
      elseif ( gridtype.eq.'rotated' ) then
197
      elseif ( gridtype.eq.'rotated' ) then
198
         print*,'Grid   clon,clat     : ',clon,clat
198
         print*,'Grid   clon,clat     : ',clon,clat
199
         print*,'       nlonlat       : ',nlonlat
199
         print*,'       nlonlat       : ',nlonlat
200
         print*,'       dlonlat       : ',dlonlat
200
         print*,'       dlonlat       : ',dlonlat
201
      endif
201
      endif
202
      print*,'Filter radius        : ',radius,' ',trim(runit)
202
      print*,'Filter radius        : ',radius,' ',trim(runit)
203
      print*,'Mode                 : ',trim(mode)
203
      print*,'Mode                 : ',trim(mode)
204
      if ( ( mode.eq.'time'  ).or.
204
      if ( ( mode.eq.'time'  ).or.
205
     >     ( mode.eq.'space' ).or.
205
     >     ( mode.eq.'space' ).or.
206
     >     (mode.eq.'grid' ) ) 
206
     >     (mode.eq.'grid' ) ) 
207
     >then
207
     >then
208
         print*,'Parameter            : ',param
208
         print*,'Parameter            : ',param
209
      endif
209
      endif
210
      if ( step.eq.0 ) then
210
      if ( step.eq.0 ) then
211
         print*,'Time step            : all'
211
         print*,'Time step            : all'
212
      elseif (step.gt.0) then
212
      elseif (step.gt.0) then
213
         print*,'Time step            : ',step
213
         print*,'Time step            : ',step
214
      endif
214
      endif
215
      print*,'Selection file       : ',trim(sel_file)
215
      print*,'Selection file       : ',trim(sel_file)
216
      print*,'Selection format     : ',trim(sel_file)
216
      print*,'Selection format     : ',trim(sel_file)
217
      print*,'Flag <crefile>       : ',crefile
217
      print*,'Flag <crefile>       : ',crefile
218
      print*,'Flag <crevar>        : ',crevar
218
      print*,'Flag <crevar>        : ',crevar
219
 
219
 
220
c     Check whether mode is valid
220
c     Check whether mode is valid
221
      if ((mode.ne.'keep'  ).and.
221
      if ((mode.ne.'keep'  ).and.
222
     >    (mode.ne.'time'  ).and.
222
     >    (mode.ne.'time'  ).and.
223
     >    (mode.ne.'space' ).and.
223
     >    (mode.ne.'space' ).and.
224
     >    (mode.ne.'grid'  ))  
224
     >    (mode.ne.'grid'  ))  
225
     >then
225
     >then
226
         print*,' ERROR: Invalid mode ',trim(mode)
226
         print*,' ERROR: Invalid mode ',trim(mode)
227
         stop
227
         stop
228
      endif
228
      endif
229
 
229
 
230
c     Allocate memory for old and new (reparameterised) trajectory
230
c     Allocate memory for old and new (reparameterised) trajectory
231
      allocate(olon(ntime),stat=stat)
231
      allocate(olon(ntime),stat=stat)
232
      if (stat.ne.0) print*,'*** error allocating array olon ***'
232
      if (stat.ne.0) print*,'*** error allocating array olon ***'
233
      allocate(olat(ntime),stat=stat)
233
      allocate(olat(ntime),stat=stat)
234
      if (stat.ne.0) print*,'*** error allocating array olat ***'
234
      if (stat.ne.0) print*,'*** error allocating array olat ***'
235
      allocate(otim(ntime),stat=stat)
235
      allocate(otim(ntime),stat=stat)
236
      if (stat.ne.0) print*,'*** error allocating array otim ***'
236
      if (stat.ne.0) print*,'*** error allocating array otim ***'
237
      allocate(nlon(1000*ntime),stat=stat)
237
      allocate(nlon(1000*ntime),stat=stat)
238
      if (stat.ne.0) print*,'*** error allocating array nlon ***'
238
      if (stat.ne.0) print*,'*** error allocating array nlon ***'
239
      allocate(nlat(1000*ntime),stat=stat)
239
      allocate(nlat(1000*ntime),stat=stat)
240
      if (stat.ne.0) print*,'*** error allocating array nlat ***'
240
      if (stat.ne.0) print*,'*** error allocating array nlat ***'
241
      allocate(ntim(1000*ntime),stat=stat)
241
      allocate(ntim(1000*ntime),stat=stat)
242
      if (stat.ne.0) print*,'*** error allocating array ntim ***'
242
      if (stat.ne.0) print*,'*** error allocating array ntim ***'
243
      allocate(odist(ntime),stat=stat)
243
      allocate(odist(ntime),stat=stat)
244
      if (stat.ne.0) print*,'*** error allocating array odist ***'
244
      if (stat.ne.0) print*,'*** error allocating array odist ***'
245
      allocate(ndist(1000*ntime),stat=stat)
245
      allocate(ndist(1000*ntime),stat=stat)
246
      if (stat.ne.0) print*,'*** error allocating array ndist ***'
246
      if (stat.ne.0) print*,'*** error allocating array ndist ***'
247
      allocate(ofld(ntime),stat=stat)
247
      allocate(ofld(ntime),stat=stat)
248
      if (stat.ne.0) print*,'*** error allocating array ofld ***'
248
      if (stat.ne.0) print*,'*** error allocating array ofld ***'
249
      allocate(nfld(1000*ntime),stat=stat)
249
      allocate(nfld(1000*ntime),stat=stat)
250
      if (stat.ne.0) print*,'*** error allocating array nfld ***'
250
      if (stat.ne.0) print*,'*** error allocating array nfld ***'
251
 
251
 
252
c     Allocate memory for complete trajectory set
252
c     Allocate memory for complete trajectory set
253
      allocate(trainp(ntra,ntime,nfield),stat=stat)
253
      allocate(trainp(ntra,ntime,nfield),stat=stat)
254
      if (stat.ne.0) print*,'*** error allocating array trainp ***'
254
      if (stat.ne.0) print*,'*** error allocating array trainp ***'
255
      allocate(sel_flag(ntra),stat=stat)
255
      allocate(sel_flag(ntra),stat=stat)
256
      if (stat.ne.0) print*,'*** error allocating array sel_flag ***'
256
      if (stat.ne.0) print*,'*** error allocating array sel_flag ***'
257
 
257
 
258
c     Allocate memory for auxiliary fields
258
c     Allocate memory for auxiliary fields
259
      allocate(traj(nfield),stat=stat)
259
      allocate(traj(nfield),stat=stat)
260
      if (stat.ne.0) print*,'*** error allocating array traj ***'
260
      if (stat.ne.0) print*,'*** error allocating array traj ***'
261
 
261
 
262
c     Set the format of the input file
262
c     Set the format of the input file
263
      call mode_tra(inpmode,inpfile)
263
      call mode_tra(inpmode,inpfile)
264
      if (inpmode.eq.-1) inpmode=1
264
      if (inpmode.eq.-1) inpmode=1
265
 
265
 
266
c     Read the input trajectory file
266
c     Read the input trajectory file
267
      call ropen_tra(fid,inpfile,ntra,ntime,nfield,
267
      call ropen_tra(fid,inpfile,ntra,ntime,nfield,
268
     >                   reftime,varsinp,inpmode)
268
     >                   reftime,varsinp,inpmode)
269
      call read_tra (fid,trainp,ntra,ntime,nfield,inpmode)
269
      call read_tra (fid,trainp,ntra,ntime,nfield,inpmode)
270
      call close_tra(fid,inpmode)
270
      call close_tra(fid,inpmode)
271
 
271
 
-
 
272
c     Bring trajectories into grid interval
-
 
273
      print*,xmin,ymin,dx,dy,nx,ny
-
 
274
      if ( ( abs(xmin+180.).lt.eps).and.
-
 
275
     >     ( abs(ymin+90. ).lt.eps).and.
-
 
276
     >     ( abs(dx-1.    ).lt.eps).and.
-
 
277
     >     ( abs(dy-1.    ).lt.eps).and.
-
 
278
     >     ( nx.eq.360    ).and.
-
 
279
     >     ( ny.eq.180    ) )
-
 
280
     >then
-
 
281
        print*,'HALLO'
-
 
282
        do i=1,ntra
-
 
283
          do j=1,ntime
-
 
284
            if ( trainp(i,j,2).lt.-180. ) then
-
 
285
                trainp(i,j,2) = trainp(i,j,2) + 360.
-
 
286
            endif
-
 
287
            if ( trainp(i,j,2).gt.180. ) then
-
 
288
                trainp(i,j,2) = trainp(i,j,2) - 360.
-
 
289
            endif
-
 
290
         enddo
-
 
291
        enddo
-
 
292
      endif
-
 
293
 
272
c     Check that first four columns correspond to time,lon,lat,p
294
c     Check that first four columns correspond to time,lon,lat,p
273
      if ( (varsinp(1).ne.'time' ).or.
295
      if ( (varsinp(1).ne.'time' ).or.
274
     >     (varsinp(2).ne.'xpos' ).and.(varsinp(2).ne.'lon' ).or.
296
     >     (varsinp(2).ne.'xpos' ).and.(varsinp(2).ne.'lon' ).or.
275
     >     (varsinp(3).ne.'ypos' ).and.(varsinp(3).ne.'lat' ).or.
297
     >     (varsinp(3).ne.'ypos' ).and.(varsinp(3).ne.'lat' ).or.
276
     >     (varsinp(4).ne.'ppos' ).and.(varsinp(4).ne.'p'   ) )
298
     >     (varsinp(4).ne.'ppos' ).and.(varsinp(4).ne.'p'   ) )
277
     >then
299
     >then
278
         print*,' ERROR: problem with input trajectories ...'
300
         print*,' ERROR: problem with input trajectories ...'
279
         stop
301
         stop
280
      endif
302
      endif
281
      varsinp(1) = 'TIME'
303
      varsinp(1) = 'TIME'
282
      varsinp(2) = 'lon'
304
      varsinp(2) = 'lon'
283
      varsinp(3) = 'lat'
305
      varsinp(3) = 'lat'
284
      varsinp(4) = 'p'
306
      varsinp(4) = 'p'
285
 
307
 
286
c     Get the index of the field (if needed)
308
c     Get the index of the field (if needed)
287
      if ( field.ne.'nil' ) then
309
      if ( field.ne.'nil' ) then
288
         ifield = 0
310
         ifield = 0
289
         do i=1,nfield
311
         do i=1,nfield
290
            if ( varsinp(i).eq.field ) ifield = i
312
            if ( varsinp(i).eq.field ) ifield = i
291
         enddo
313
         enddo
292
         if ( ifield.eq.0 ) then
314
         if ( ifield.eq.0 ) then
293
            print*,' ERROR: field ',trim(field),' not found... Stop'
315
            print*,' ERROR: field ',trim(field),' not found... Stop'
294
            stop
316
            stop
295
         endif
317
         endif
296
      endif
318
      endif
297
 
319
 
298
c     Write some status information of the input trajectories
320
c     Write some status information of the input trajectories
299
      print*
321
      print*
300
      print*,'---- INPUT TRAJECTORIES ---------------------------------'
322
      print*,'---- INPUT TRAJECTORIES ---------------------------------'
301
      print*
323
      print*
302
      print*,' Reference time (year)  : ',reftime(1)
324
      print*,' Reference time (year)  : ',reftime(1)
303
      print*,'                (month) : ',reftime(2)
325
      print*,'                (month) : ',reftime(2)
304
      print*,'                (day)   : ',reftime(3)
326
      print*,'                (day)   : ',reftime(3)
305
      print*,'                (hour)  : ',reftime(4)
327
      print*,'                (hour)  : ',reftime(4)
306
      print*,'                (min)   : ',reftime(5)
328
      print*,'                (min)   : ',reftime(5)
307
      print*,' Time range (min)       : ',reftime(6)
329
      print*,' Time range (min)       : ',reftime(6)
308
      do i=1,nfield
330
      do i=1,nfield
309
         if ( i.ne.ifield ) then
331
         if ( i.ne.ifield ) then
310
            print*,' Var                    :',i,trim(varsinp(i))
332
            print*,' Var                    :',i,trim(varsinp(i))
311
         else
333
         else
312
            print*,' Var                    :',i,trim(varsinp(i)),
334
            print*,' Var                    :',i,trim(varsinp(i)),
313
     >                                        '       [ gridding ]'
335
     >                                        '       [ gridding ]'
314
         endif
336
         endif
315
      enddo
337
      enddo
316
      print*,' List of selected times'
338
      print*,' List of selected times'
317
      do i=1,ntime
339
      do i=1,ntime
318
         if ( (step.eq.0).or.(step.eq.i) ) then
340
         if ( (step.eq.0).or.(step.eq.i) ) then
319
            print*,'     ',i,'  -> ',trainp(1,i,1)
341
            print*,'     ',i,'  -> ',trainp(1,i,1)
320
         endif
342
         endif
321
      enddo
343
      enddo
322
      print*
344
      print*
323
 
345
 
324
c     Select flag: all trajectories are selected
346
c     Select flag: all trajectories are selected
325
      if ( sel_file.eq.'nil' ) then
347
      if ( sel_file.eq.'nil' ) then
326
 
348
 
327
         do i=1,ntra
349
         do i=1,ntra
328
            sel_flag(i) = 1
350
            sel_flag(i) = 1
329
         enddo
351
         enddo
330
 
352
 
331
c     Select flag: index file
353
c     Select flag: index file
332
      elseif ( sel_format.eq.'index' ) then
354
      elseif ( sel_format.eq.'index' ) then
333
 
355
 
334
         do i=1,ntra
356
         do i=1,ntra
335
            sel_flag(i) = 0
357
            sel_flag(i) = 0
336
         enddo
358
         enddo
337
         
359
         
338
         open(10,file=sel_file)
360
         open(10,file=sel_file)
339
 142      read(10,*,end=141) ind
361
 142      read(10,*,end=141) ind
340
          sel_flag(ind) = 1
362
          sel_flag(ind) = 1
341
          goto 142 
363
          goto 142 
342
 141     continue
364
 141     continue
343
         close(10)
365
         close(10)
344
 
366
 
345
c     Select flag: boolean file
367
c     Select flag: boolean file
346
      elseif ( sel_format.eq.'boolean' ) then
368
      elseif ( sel_format.eq.'boolean' ) then
347
       
369
       
348
         open(10,file=sel_file)
370
         open(10,file=sel_file)
349
          do i=1,ntra
371
          do i=1,ntra
350
            read(10,*) ind
372
            read(10,*) ind
351
            if ( ind.eq.1 ) sel_flag(i) = ind
373
            if ( ind.eq.1 ) sel_flag(i) = ind
352
          enddo
374
          enddo
353
         close(10)
375
         close(10)
354
         
376
         
355
      endif
377
      endif
356
 
378
 
357
c     Write status information
379
c     Write status information
358
      if ( sel_file.eq.'nil' ) then
380
      if ( sel_file.eq.'nil' ) then
359
          print*,' Selected trajectories  : all ',ntra          
381
          print*,' Selected trajectories  : all ',ntra          
360
       else
382
       else
361
          count = 0
383
          count = 0
362
          do i=1,ntra
384
          do i=1,ntra
363
             if ( sel_flag(i).eq.1 ) count = count + 1
385
             if ( sel_flag(i).eq.1 ) count = count + 1
364
          enddo
386
          enddo
365
          print*,' #selected trajectories : ',count,
387
          print*,' #selected trajectories : ',count,
366
     >            ' [ ',real(count)/real(ntra) * 100.,' % ] '
388
     >            ' [ ',real(count)/real(ntra) * 100.,' % ] '
367
       endif
389
       endif
368
       print*
390
       print*
369
 
391
 
370
c     ---------------------------------------------------------------------
392
c     ---------------------------------------------------------------------
371
c     Coordinate transformations and grid adjustment
393
c     Coordinate transformations and grid adjustment
372
c     ---------------------------------------------------------------------
394
c     ---------------------------------------------------------------------
373
 
395
 
374
c     Transform from lat/lon to rotated lat/lon, if requested
396
c     Transform from lat/lon to rotated lat/lon, if requested
375
      if ( gridtype.eq.'rotated') then
397
      if ( gridtype.eq.'rotated') then
376
 
398
 
377
         crot = 0.
399
         crot = 0.
378
 
400
 
379
         pollon=clon-180.
401
         pollon=clon-180.
380
         if (pollon.lt.-180.) pollon=pollon+360.
402
         if (pollon.lt.-180.) pollon=pollon+360.
381
         pollat=90.-clat
403
         pollat=90.-clat
382
         do i=1,ntra
404
         do i=1,ntra
383
            do j=1,ntime
405
            do j=1,ntime
384
               
406
               
385
               if ( sel_flag(i).eq.1 ) then
407
               if ( sel_flag(i).eq.1 ) then
386
 
408
 
387
c                Get lat/lon coordinates for trajectory point
409
c                Get lat/lon coordinates for trajectory point
388
                 lon = trainp(i,j,2)
410
                 lon = trainp(i,j,2)
389
                 lat = trainp(i,j,3)
411
                 lat = trainp(i,j,3)
390
 
412
 
391
c                First Rotation
413
c                First Rotation
392
                 pollon=clon-180.
414
                 pollon=clon-180.
393
                 if (pollon.lt.-180.) pollon=pollon+360.
415
                 if (pollon.lt.-180.) pollon=pollon+360.
394
                 pollat=90.-clat
416
                 pollat=90.-clat
395
                 rlon0=lmtolms(lat,lon,pollat,pollon)
417
                 rlon0=lmtolms(lat,lon,pollat,pollon)
396
                 rlat0=phtophs(lat,lon,pollat,pollon)            
418
                 rlat0=phtophs(lat,lon,pollat,pollon)            
397
 
419
 
398
c                Second rotation
420
c                Second rotation
399
                 pollon=-180.
421
                 pollon=-180.
400
                 pollat=90.+crot
422
                 pollat=90.+crot
401
                 rlon=90.+lmtolms(rlat0,rlon0-90.,pollat,pollon)
423
                 rlon=90.+lmtolms(rlat0,rlon0-90.,pollat,pollon)
402
                 rlat=phtophs(rlat0,rlon0-90.,pollat,pollon)   
424
                 rlat=phtophs(rlat0,rlon0-90.,pollat,pollon)   
403
 
425
 
404
c                Get rotated latitude and longitude
426
c                Get rotated latitude and longitude
405
 100             if (rlon.lt.xmin) then
427
 100             if (rlon.lt.xmin) then
406
                  rlon=rlon+360.
428
                  rlon=rlon+360.
407
                  goto 100
429
                  goto 100
408
                 endif
430
                 endif
409
 102             if (rlon.gt.(xmin+real(nx-1)*dx)) then
431
 102             if (rlon.gt.(xmin+real(nx-1)*dx)) then
410
                  rlon=rlon-360.
432
                  rlon=rlon-360.
411
                  goto 102
433
                  goto 102
412
                 endif
434
                 endif
413
 
435
 
414
c                Set the new trajectory coordinates
436
c                Set the new trajectory coordinates
415
                 trainp(i,j,2) = rlon
437
                 trainp(i,j,2) = rlon
416
                 trainp(i,j,3) = rlat
438
                 trainp(i,j,3) = rlat
417
 
439
 
418
              endif
440
              endif
419
 
441
 
420
            enddo
442
            enddo
421
         enddo
443
         enddo
422
            
444
            
423
      endif
445
      endif
424
 
446
 
425
c     Dynamic grid adjustment
447
c     Dynamic grid adjustment
426
      if ( dynamic_grid.eq.1 ) then
448
      if ( dynamic_grid.eq.1 ) then
427
 
449
 
428
c        Get the grid parameters
450
c        Get the grid parameters
429
         xmin =  180.
451
         xmin =  180.
430
         ymin =   90.
452
         ymin =   90.
431
         xmax = -180.
453
         xmax = -180.
432
         ymax =  -90.
454
         ymax =  -90.
433
 
455
 
434
         do i=1,ntra
456
         do i=1,ntra
435
 
457
 
436
            if ( sel_flag(i).eq.1 ) then
458
            if ( sel_flag(i).eq.1 ) then
437
 
459
 
438
              if ( step.eq.0 ) then
460
              if ( step.eq.0 ) then
439
               do j=1,ntime
461
               do j=1,ntime
440
                  if ( trainp(i,j,2).lt.xmin) xmin =  trainp(i,j,2)
462
                  if ( trainp(i,j,2).lt.xmin) xmin =  trainp(i,j,2)
441
                  if ( trainp(i,j,2).gt.xmax) xmax =  trainp(i,j,2)
463
                  if ( trainp(i,j,2).gt.xmax) xmax =  trainp(i,j,2)
442
                  if ( trainp(i,j,3).lt.ymin) ymin =  trainp(i,j,3)
464
                  if ( trainp(i,j,3).lt.ymin) ymin =  trainp(i,j,3)
443
                  if ( trainp(i,j,3).gt.ymax) ymax =  trainp(i,j,3)
465
                  if ( trainp(i,j,3).gt.ymax) ymax =  trainp(i,j,3)
444
               enddo
466
               enddo
445
              else
467
              else
446
                if ( trainp(i,step,2).lt.xmin) xmin =  trainp(i,step,2)
468
                if ( trainp(i,step,2).lt.xmin) xmin =  trainp(i,step,2)
447
                if ( trainp(i,step,2).gt.xmax) xmax =  trainp(i,step,2)
469
                if ( trainp(i,step,2).gt.xmax) xmax =  trainp(i,step,2)
448
                if ( trainp(i,step,3).lt.ymin) ymin =  trainp(i,step,3)
470
                if ( trainp(i,step,3).lt.ymin) ymin =  trainp(i,step,3)
449
                if ( trainp(i,step,3).gt.ymax) ymax =  trainp(i,step,3)
471
                if ( trainp(i,step,3).gt.ymax) ymax =  trainp(i,step,3)
450
              endif
472
              endif
451
            
473
            
452
            endif
474
            endif
453
 
475
 
454
         enddo
476
         enddo
455
 
477
 
456
c        Get first guess for "optimal" grid
478
c        Get first guess for "optimal" grid
457
         nx = 400
479
         nx = 400
458
         ny = 400
480
         ny = 400
459
         dx = (xmax - xmin)/real(nx-1)
481
         dx = (xmax - xmin)/real(nx-1)
460
         dy = (ymax - ymin)/real(ny-1)
482
         dy = (ymax - ymin)/real(ny-1)
461
 
483
 
462
c        Make the grid spacing equal in zonal and meridional direction
484
c        Make the grid spacing equal in zonal and meridional direction
463
         if ( dx.gt.dy ) then
485
         if ( dx.gt.dy ) then
464
            
486
            
465
            dy = dx
487
            dy = dx
466
            ny = (ymax - ymin)/dy + 1
488
            ny = (ymax - ymin)/dy + 1
467
            if (ny.lt.nx/2)              ny = nx / 2
489
            if (ny.lt.nx/2)              ny = nx / 2
468
            if ( real(ny)*dy .ge. 180. ) ny = 180./dy + 1
490
            if ( real(ny)*dy .ge. 180. ) ny = 180./dy + 1
469
            ycen = 0.5* (ymin+ymax)
491
            ycen = 0.5* (ymin+ymax)
470
            ymin = ycen - 0.5 * real(ny/2) * dy
492
            ymin = ycen - 0.5 * real(ny/2) * dy
471
            if (ymin.le.-90.) ymin = -90.
493
            if (ymin.le.-90.) ymin = -90.
472
 
494
 
473
         else
495
         else
474
               
496
               
475
            dx = dy
497
            dx = dy
476
            nx = (xmax - xmin)/dx + 1
498
            nx = (xmax - xmin)/dx + 1
477
            if (nx.lt.ny/2)              nx = ny / 2
499
            if (nx.lt.ny/2)              nx = ny / 2
478
            if ( real(nx)*dx .ge. 360. ) nx = 360./dx + 1
500
            if ( real(nx)*dx .ge. 360. ) nx = 360./dx + 1
479
            xcen = 0.5* (xmin+xmax)
501
            xcen = 0.5* (xmin+xmax)
480
            xmin = xcen - 0.5 * real(nx/2) * dx
502
            xmin = xcen - 0.5 * real(nx/2) * dx
481
            if (xmin.le.-180.) xmin = -180.
503
            if (xmin.le.-180.) xmin = -180.
482
 
504
 
483
         endif
505
         endif
484
            
506
            
485
c        Write information
507
c        Write information
486
         print*
508
         print*
487
         print*,'---- DYNAMIC GRID ADJUSTMENT',
509
         print*,'---- DYNAMIC GRID ADJUSTMENT',
488
     >          ' ----------------------------'  
510
     >          ' ----------------------------'  
489
         print*
511
         print*
490
         print*,'Grid   nlon,nlat     : ',nx,ny
512
         print*,'Grid   nlon,nlat     : ',nx,ny
491
         print*,'       lonmin,latmin : ',xmin,ymin
513
         print*,'       lonmin,latmin : ',xmin,ymin
492
         print*,'       dlon,dlat     : ',dx,dy
514
         print*,'       dlon,dlat     : ',dx,dy
493
         print*
515
         print*
494
 
516
 
495
c     Write grid information for rotated grid (if not already done
517
c     Write grid information for rotated grid (if not already done
496
      elseif ( gridtype.eq.'rotated') then
518
      elseif ( gridtype.eq.'rotated') then
497
         
519
         
498
         print*
520
         print*
499
         print*,'---- GRID PARAMETERS -------',
521
         print*,'---- GRID PARAMETERS -------',
500
     >          ' ----------------------------'  
522
     >          ' ----------------------------'  
501
         print*
523
         print*
502
         print*,'Grid   nlon,nlat     : ',nx,ny
524
         print*,'Grid   nlon,nlat     : ',nx,ny
503
         print*,'       lonmin,latmin : ',xmin,ymin
525
         print*,'       lonmin,latmin : ',xmin,ymin
504
         print*,'       dlon,dlat     : ',dx,dy
526
         print*,'       dlon,dlat     : ',dx,dy
505
         print*
527
         print*
506
       
528
       
507
 
529
 
508
      endif
530
      endif
509
 
531
 
510
c     Set the grid boundaries
532
c     Set the grid boundaries
511
      xmax=xmin+real(nx-1)*dx
533
      xmax=xmin+real(nx-1)*dx
512
      ymax=ymin+real(ny-1)*dy
534
      ymax=ymin+real(ny-1)*dy
513
 
535
 
514
c     Allocate memory for output array and auxiliary gridding array 
536
c     Allocate memory for output array and auxiliary gridding array 
515
      allocate(cnt(nx,ny),stat=stat)
537
      allocate(cnt(nx,ny),stat=stat)
516
      if (stat.ne.0) print*,'*** error allocating array cnt  ***'
538
      if (stat.ne.0) print*,'*** error allocating array cnt  ***'
517
      allocate(res(nx,ny),stat=stat)
539
      allocate(res(nx,ny),stat=stat)
518
      if (stat.ne.0) print*,'*** error allocating array res  ***'
540
      if (stat.ne.0) print*,'*** error allocating array res  ***'
519
      allocate(fld(nx,ny),stat=stat)
541
      allocate(fld(nx,ny),stat=stat)
520
      if (stat.ne.0) print*,'*** error allocating array fld  ***'
542
      if (stat.ne.0) print*,'*** error allocating array fld  ***'
521
      allocate(area(nx,ny),stat=stat)
543
      allocate(area(nx,ny),stat=stat)
522
      if (stat.ne.0) print*,'*** error allocating array area ***'
544
      if (stat.ne.0) print*,'*** error allocating array area ***'
523
 
545
 
524
      allocate(connect0(nx,ny),stat=stat)
546
      allocate(connect0(nx,ny),stat=stat)
525
      if (stat.ne.0) print*,'*** error allocating array connect0 ***'
547
      if (stat.ne.0) print*,'*** error allocating array connect0 ***'
526
      allocate(connect1(nx,ny),stat=stat)
548
      allocate(connect1(nx,ny),stat=stat)
527
      if (stat.ne.0) print*,'*** error allocating array connect1 ***'
549
      if (stat.ne.0) print*,'*** error allocating array connect1 ***'
528
      allocate(connect2(nx,ny),stat=stat)
550
      allocate(connect2(nx,ny),stat=stat)
529
      if (stat.ne.0) print*,'*** error allocating array connect2 ***'
551
      if (stat.ne.0) print*,'*** error allocating array connect2 ***'
530
 
552
 
531
 
553
 
532
c     Init the output array
554
c     Init the output array
533
      do i=1,nx
555
      do i=1,nx
534
         do j=1,ny
556
         do j=1,ny
535
            connect0(i,j) = 0
557
            connect0(i,j) = 0
536
            connect1(i,j) = 0
558
            connect1(i,j) = 0
537
            connect2(i,j) = 0
559
            connect2(i,j) = 0
538
            cnt(i,j)      = 0.
560
            cnt(i,j)      = 0.
539
            res(i,j)      = 0.
561
            res(i,j)      = 0.
540
            fld(i,j)      = 0.
562
            fld(i,j)      = 0.
541
         enddo
563
         enddo
542
      enddo  
564
      enddo  
543
 
565
 
544
c     ---------------------------------------------------------------------
566
c     ---------------------------------------------------------------------
545
c     Gridding
567
c     Gridding
546
c     ---------------------------------------------------------------------
568
c     ---------------------------------------------------------------------
547
 
569
 
548
c     Write some status information 
570
c     Write some status information 
549
      print*,'---- GRIDDING -------------------------------------------'
571
      print*,'---- GRIDDING -------------------------------------------'
550
      print*
572
      print*
551
 
573
 
552
c     Loop over all entries of sampling table
574
c     Loop over all entries of sampling table
553
      connectval0 = 0
575
      connectval0 = 0
554
      connectval1 = 0
576
      connectval1 = 0
555
      connectval2 = 0
577
      connectval2 = 0
556
      count       = 0
578
      count       = 0
557
 
579
 
558
      do i=1,ntra
580
      do i=1,ntra
559
 
581
 
560
         if (mod(i,100).eq.0) print*,i,' of ',ntra
582
         if (mod(i,100).eq.0) print*,i,' of ',ntra
561
 
583
 
562
c        Skip all trajectories which are not selected
584
c        Skip all trajectories which are not selected
563
         if ( sel_flag(i).eq.0 ) goto 300
585
         if ( sel_flag(i).eq.0 ) goto 300
564
 
586
 
565
c        ------- Read a complete trajectory ---------------------------
587
c        ------- Read a complete trajectory ---------------------------
566
         do j=1,ntime
588
         do j=1,ntime
567
            otim(j) = trainp(i,j,1)
589
            otim(j) = trainp(i,j,1)
568
            olon(j) = trainp(i,j,2)
590
            olon(j) = trainp(i,j,2)
569
            olat(j) = trainp(i,j,3)
591
            olat(j) = trainp(i,j,3)
570
            if ( field.ne.'nil' ) then
592
            if ( field.ne.'nil' ) then
571
               ofld(j) =trainp(i,j,ifield)
593
               ofld(j) =trainp(i,j,ifield)
572
            endif
594
            endif
573
         enddo
595
         enddo
574
 
596
 
575
c        -------- Convert hh.m time into fractional time --------------
597
c        -------- Convert hh.m time into fractional time --------------
576
         do j=1,ntime
598
         do j=1,ntime
577
            hhmm    = otim(j)
599
            hhmm    = otim(j)
578
            call hhmm2frac (hhmm,frac)
600
            call hhmm2frac (hhmm,frac)
579
            otim(j) = frac
601
            otim(j) = frac
580
         enddo
602
         enddo
581
 
603
 
582
c        -------- Interpolation ---------------------------------------
604
c        -------- Interpolation ---------------------------------------
583
 
605
 
584
c        Keep the trajectory points as they are
606
c        Keep the trajectory points as they are
585
         if ( ( mode.eq.'keep').and.(step.eq.0) ) then
607
         if ( ( mode.eq.'keep').and.(step.eq.0) ) then
586
            npts=opts
608
            npts=opts
587
            do j=1,opts
609
            do j=1,opts
588
               ntim(j)=otim(j)
610
               ntim(j)=otim(j)
589
               nlon(j)=olon(j)
611
               nlon(j)=olon(j)
590
               nlat(j)=olat(j)
612
               nlat(j)=olat(j)
591
               if ( field.ne.'nil' ) then
613
               if ( field.ne.'nil' ) then
592
                  nfld(j)=ofld(j)
614
                  nfld(j)=ofld(j)
593
               endif
615
               endif
594
            enddo
616
            enddo
595
 
617
 
596
c        Select a single time step
618
c        Select a single time step
597
         elseif ( ( mode.eq.'keep').and.(step.gt.0) ) then
619
         elseif ( ( mode.eq.'keep').and.(step.gt.0) ) then
598
            npts    = 1
620
            npts    = 1
599
            ntim(1) = otim(step)
621
            ntim(1) = otim(step)
600
            nlon(1) = olon(step)
622
            nlon(1) = olon(step)
601
            nlat(1) = olat(step)
623
            nlat(1) = olat(step)
602
            if ( field.ne.'nil' ) then
624
            if ( field.ne.'nil' ) then
603
               nfld(1) = ofld(step)
625
               nfld(1) = ofld(step)
604
            endif
626
            endif
605
 
627
 
606
c        Perform a reparameterisation in time
628
c        Perform a reparameterisation in time
607
         else if ( (mode.eq.'time').and.(step.eq.0) ) then
629
         else if ( (mode.eq.'time').and.(step.eq.0) ) then
608
 
630
 
609
c           Get the new number of trajectory points
631
c           Get the new number of trajectory points
610
            npts=nint(abs(otim(opts)-otim(1))/param)+1
632
            npts=nint(abs(otim(opts)-otim(1))/param)+1
611
 
633
 
612
c           Handle date line problem
634
c           Handle date line problem
613
            do j=2,opts
635
            do j=2,opts
614
               if ( (olon(j-1)-olon(j)).gt.180. ) then
636
               if ( (olon(j-1)-olon(j)).gt.180. ) then
615
                  olon(j) = olon(j) + 360.
637
                  olon(j) = olon(j) + 360.
616
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
638
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
617
                  olon(j) = olon(j) - 360.
639
                  olon(j) = olon(j) - 360.
618
               endif
640
               endif
619
            enddo
641
            enddo
620
 
642
 
621
c           Cubic spline fitting
643
c           Cubic spline fitting
622
            call curvefit(otim,olon,opts,ntim,nlon,npts)
644
            call curvefit(otim,olon,opts,ntim,nlon,npts)
623
            call curvefit(otim,olat,opts,ntim,nlat,npts)
645
            call curvefit(otim,olat,opts,ntim,nlat,npts)
624
            if ( field.ne.'nil' ) then
646
            if ( field.ne.'nil' ) then
625
               call curvefit(otim,ofld,opts,ntim,nfld,npts)
647
               call curvefit(otim,ofld,opts,ntim,nfld,npts)
626
            endif
648
            endif
627
 
649
 
628
c           Reverse date line handling
650
c           Reverse date line handling
629
            do j=1,npts
651
            do j=1,npts
630
               if ( nlon(j).gt.xmax ) then
652
               if ( nlon(j).gt.xmax ) then
631
                  nlon(j) = nlon(j) -360.
653
                  nlon(j) = nlon(j) -360.
632
               else if ( nlon(j).lt.xmin ) then
654
               else if ( nlon(j).lt.xmin ) then
633
                  nlon(j) = nlon(j) +360.
655
                  nlon(j) = nlon(j) +360.
634
               endif
656
               endif
635
            enddo
657
            enddo
636
 
658
 
637
c        Perform a reparameterisation with equally spaced gridpoint
659
c        Perform a reparameterisation with equally spaced gridpoint
638
         elseif ( (mode.eq.'space').and.(step.eq.0) ) then
660
         elseif ( (mode.eq.'space').and.(step.eq.0) ) then
639
            
661
            
640
c           Calculate the distance and spacing
662
c           Calculate the distance and spacing
641
            odist(1) = 0.
663
            odist(1) = 0.
642
            unit     = 'km'
664
            unit     = 'km'
643
            do j=2,ntime
665
            do j=2,ntime
644
               odist(j)=odist(j-1) + 
666
               odist(j)=odist(j-1) + 
645
     >                  sdis(olon(j-1),olat(j-1),olon(j),olat(j),unit)
667
     >                  sdis(olon(j-1),olat(j-1),olon(j),olat(j),unit)
646
            enddo
668
            enddo
647
            
669
            
648
c           Determine the new number of trajectory points
670
c           Determine the new number of trajectory points
649
            npts=nint(odist(ntime)/param)+1
671
            npts=nint(odist(ntime)/param)+1
650
            if (npts.eq.0) then
672
            if (npts.eq.0) then
651
               npts=1.
673
               npts=1.
652
            endif
674
            endif
653
        
675
        
654
c           Handle date line problem
676
c           Handle date line problem
655
            do j=2,opts
677
            do j=2,opts
656
               if ( (olon(j-1)-olon(j)).gt.180. ) then
678
               if ( (olon(j-1)-olon(j)).gt.180. ) then
657
                  olon(j) = olon(j) + 360.
679
                  olon(j) = olon(j) + 360.
658
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
680
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
659
                  olon(j) = olon(j) - 360.
681
                  olon(j) = olon(j) - 360.
660
               endif
682
               endif
661
            enddo
683
            enddo
662
                  
684
                  
663
c           Cubic spline fitting
685
c           Cubic spline fitting
664
            call curvefit(odist,olon,opts,ndist,nlon,npts)
686
            call curvefit(odist,olon,opts,ndist,nlon,npts)
665
            call curvefit(odist,olat,opts,ndist,nlat,npts)
687
            call curvefit(odist,olat,opts,ndist,nlat,npts)
666
            call curvefit(odist,otim,opts,ndist,ntim,npts)
688
            call curvefit(odist,otim,opts,ndist,ntim,npts)
667
            if ( field.ne.'nil' ) then
689
            if ( field.ne.'nil' ) then
668
               call curvefit(odist,ofld,opts,ndist,nfld,npts)
690
               call curvefit(odist,ofld,opts,ndist,nfld,npts)
669
            endif
691
            endif
670
 
692
 
671
c           Reverse date line handling
693
c           Reverse date line handling
672
            do j=1,npts
694
            do j=1,npts
673
               if ( nlon(j).gt.xmax ) then
695
               if ( nlon(j).gt.xmax ) then
674
                  nlon(j) = nlon(j) -360.
696
                  nlon(j) = nlon(j) -360.
675
               else if ( nlon(j).lt.xmin ) then
697
               else if ( nlon(j).lt.xmin ) then
676
                  nlon(j) = nlon(j) +360.
698
                  nlon(j) = nlon(j) +360.
677
               endif
699
               endif
678
            enddo
700
            enddo
679
 
701
 
680
c        Perform a reparameterisation with equally spaced gridpoint
702
c        Perform a reparameterisation with equally spaced gridpoint
681
         elseif ( (mode.eq.'grid').and.(step.eq.0) ) then
703
         elseif ( (mode.eq.'grid').and.(step.eq.0) ) then
682
            
704
            
683
c           Calculate the distance and spacing
705
c           Calculate the distance and spacing
684
            odist(1) = 0.
706
            odist(1) = 0.
685
            unit     = 'deg'
707
            unit     = 'deg'
686
            do j=2,ntime
708
            do j=2,ntime
687
               odist(j)=odist(j-1) + 
709
               odist(j)=odist(j-1) + 
688
     >                  sdis(olon(j-1),olat(j-1),olon(j),olat(j),unit)
710
     >                  sdis(olon(j-1),olat(j-1),olon(j),olat(j),unit)
689
            enddo
711
            enddo
690
            
712
            
691
c           Determine the new number of trajectory points
713
c           Determine the new number of trajectory points
692
            npts=nint(odist(ntime)/param)+1
714
            npts=nint(odist(ntime)/param)+1
693
            if (npts.eq.0) then
715
            if (npts.eq.0) then
694
               npts=1.
716
               npts=1.
695
            endif
717
            endif
696
        
718
        
697
c           Handle date line problem
719
c           Handle date line problem
698
            do j=2,opts
720
            do j=2,opts
699
               if ( (olon(j-1)-olon(j)).gt.180. ) then
721
               if ( (olon(j-1)-olon(j)).gt.180. ) then
700
                  olon(j) = olon(j) + 360.
722
                  olon(j) = olon(j) + 360.
701
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
723
               else if ( (olon(j-1)-olon(j)).lt.-180. ) then
702
                  olon(j) = olon(j) - 360.
724
                  olon(j) = olon(j) - 360.
703
               endif
725
               endif
704
            enddo
726
            enddo
705
                  
727
                  
706
c           Cubic spline fitting
728
c           Cubic spline fitting
707
            call curvefit(odist,olon,opts,ndist,nlon,npts)
729
            call curvefit(odist,olon,opts,ndist,nlon,npts)
708
            call curvefit(odist,olat,opts,ndist,nlat,npts)
730
            call curvefit(odist,olat,opts,ndist,nlat,npts)
709
            call curvefit(odist,otim,opts,ndist,ntim,npts)
731
            call curvefit(odist,otim,opts,ndist,ntim,npts)
710
            if ( field.ne.'nil' ) then
732
            if ( field.ne.'nil' ) then
711
               call curvefit(odist,ofld,opts,ndist,nfld,npts)
733
               call curvefit(odist,ofld,opts,ndist,nfld,npts)
712
            endif
734
            endif
713
 
735
 
714
c           Reverse date line handling
736
c           Reverse date line handling
715
            do j=1,npts
737
            do j=1,npts
716
               if ( nlon(j).gt.xmax ) then
738
               if ( nlon(j).gt.xmax ) then
717
                  nlon(j) = nlon(j) -360.
739
                  nlon(j) = nlon(j) -360.
718
               else if ( nlon(j).lt.xmin ) then
740
               else if ( nlon(j).lt.xmin ) then
719
                  nlon(j) = nlon(j) +360.
741
                  nlon(j) = nlon(j) +360.
720
               endif
742
               endif
721
            enddo
743
            enddo
722
 
744
 
723
         endif
745
         endif
724
 
746
 
725
c        -------- Do the gridding -------------------------------------
747
c        -------- Do the gridding -------------------------------------
726
 
748
 
727
c        Gridding of trajectory
749
c        Gridding of trajectory
728
         do j=1,npts
750
         do j=1,npts
729
 
751
 
730
c           Check whether point is in data domain
752
c           Check whether point is in data domain
731
	    if ( (nlon(j).gt.xmin).and.(nlon(j).lt.xmax).and.
753
	    if ( (nlon(j).gt.xmin).and.(nlon(j).lt.xmax).and.
732
     >           (nlat(j).gt.ymin).and.(nlat(j).lt.ymax))
754
     >       (nlat(j).gt.ymin).and.(nlat(j).lt.ymax))
733
     >      then
755
     >      then
734
 
756
 
735
c              Increase counter for gridded points
757
c              Increase counter for gridded points
736
               count = count + 1
758
               count = count + 1
737
 
759
 
738
c              ----------------- Gridding: simple count -----------------
760
c              ----------------- Gridding: simple count -----------------
739
               connectval0 = connectval0+1
761
               connectval0 = connectval0+1
740
               
762
               
741
               addvalue    = 1.
763
               addvalue    = 1.
742
               
764
               
743
               call  gridding1
765
               call  gridding1
744
     >              (nlat(j),nlon(j),addvalue,
766
     >              (nlat(j),nlon(j),addvalue,
745
     >               radius,runit,connect0,connectval0,
767
     >               radius,runit,connect0,connectval0,
746
     >               cnt,nx,ny,xmin,ymin,dx,dy)
768
     >               cnt,nx,ny,xmin,ymin,dx,dy)
747
 
769
 
748
c              ----------------- Gridding: residence time ---------------
770
c              ----------------- Gridding: residence time ---------------
749
               connectval1 = connectval1+1
771
               connectval1 = connectval1+1
750
               
772
               
751
               if ( ntime.eq.1 ) then
773
               if ( ntime.eq.1 ) then
752
                  addvalue = 0.
774
                  addvalue = 0.
753
               elseif ( j.eq.1 )  then
775
               elseif ( j.eq.1 )  then
754
                  addvalue=abs(ntim(2)-ntim(1))
776
                  addvalue=abs(ntim(2)-ntim(1))
755
               else
777
               else
756
                  addvalue=abs(ntim(j)-ntim(j-1))
778
                  addvalue=abs(ntim(j)-ntim(j-1))
757
               endif
779
               endif
758
               
780
               
759
               call  gridding1
781
               call  gridding1
760
     >              (nlat(j),nlon(j),addvalue,
782
     >              (nlat(j),nlon(j),addvalue,
761
     >               radius,runit,connect1,connectval1,
783
     >               radius,runit,connect1,connectval1,
762
     >               res,nx,ny,xmin,ymin,dx,dy)
784
     >               res,nx,ny,xmin,ymin,dx,dy)
763
 
785
 
764
 
786
 
765
c              --------------- Gridding: field -------------------------
787
c              --------------- Gridding: field -------------------------
766
               if ( field.ne.'nil' ) then
788
               if ( field.ne.'nil' ) then
767
 
789
 
768
                   connectval2 = connectval2+1
790
                   connectval2 = connectval2+1
769
               
791
               
770
                   addvalue    = nfld(j)
792
                   addvalue    = nfld(j)
771
               
793
               
772
                   call  gridding1
794
                   call  gridding1
773
     >                  (nlat(j),nlon(j),addvalue,
795
     >                  (nlat(j),nlon(j),addvalue,
774
     >                  radius,runit,connect2,connectval2,
796
     >                  radius,runit,connect2,connectval2,
775
     >                  fld,nx,ny,xmin,ymin,dx,dy)
797
     >                  fld,nx,ny,xmin,ymin,dx,dy)
776
 
798
 
777
               endif
799
               endif
778
 
800
 
779
	    endif
801
	    endif
780
 
802
 
781
         enddo
803
         enddo
782
 
804
 
783
c        Exit point for loop over all trajectories
805
c        Exit point for loop over all trajectories
784
 300     continue
806
 300     continue
785
 
807
 
786
      enddo
808
      enddo
787
 
809
 
788
c     Write status information
810
c     Write status information
789
      print*
811
      print*
790
      print*,' # gridded points       : ',count
812
      print*,' # gridded points       : ',count
791
 
813
 
792
c     ---------------------------------------------------------------------
814
c     ---------------------------------------------------------------------
793
c     Unit conversions and output to netCDF file
815
c     Unit conversions and output to netCDF file
794
c     ---------------------------------------------------------------------
816
c     ---------------------------------------------------------------------
795
 
817
 
796
c     Write some status information 
818
c     Write some status information 
797
      print*
819
      print*
798
      print*,'---- WRITE OUTPUT ---------------------------------------'
820
      print*,'---- WRITE OUTPUT ---------------------------------------'
799
      print*
821
      print*
800
 
822
 
801
c     Area (in km^2)
823
c     Area (in km^2)
802
      do i=1,nx	         
824
      do i=1,nx	         
803
         do j=1,ny	
825
         do j=1,ny	
804
            slat=ymin+real(j-1)*dy
826
            slat=ymin+real(j-1)*dy
805
            if (abs(abs(slat)-90.).gt.eps) then
827
            if (abs(abs(slat)-90.).gt.eps) then
806
               area(i,j) = dy*dx*cos(pi180*slat)*deltay**2
828
               area(i,j) = dy*dx*cos(pi180*slat)*deltay**2
807
            else
829
            else
808
               area(i,j) = 0.
830
               area(i,j) = 0.
809
            endif
831
            endif
810
         enddo
832
         enddo
811
      enddo
833
      enddo
812
 
834
 
813
c     Normalise gridded field
835
c     Normalise gridded field
814
      if ( field.ne.'nil' ) then
836
      if ( field.ne.'nil' ) then
815
         do i=1,nx
837
         do i=1,nx
816
            do j=1,ny
838
            do j=1,ny
817
               if ( cnt(i,j).gt.0. ) then
839
               if ( cnt(i,j).gt.0. ) then
818
                  fld(i,j) = fld(i,j) / cnt(i,j)
840
                  fld(i,j) = fld(i,j) / cnt(i,j)
819
               endif
841
               endif
820
            enddo
842
            enddo
821
         enddo
843
         enddo
822
      endif
844
      endif
823
 
845
 
824
c     Set the time for the output netCDF files - if a composite is
846
c     Set the time for the output netCDF files - if a composite is
825
c     calculatd, then the time is set to 
847
c     calculatd, then the time is set to 
826
      if ( step.eq.0 ) then
848
      if ( step.eq.0 ) then
827
         time = -999.
849
         time = -999.
828
         print*,'   ... COMPOSITE OVER ALL TRAJECTORY TIMES (-999)'
850
         print*,'   ... COMPOSITE OVER ALL TRAJECTORY TIMES (-999)'
829
         print*
851
         print*
830
      else
852
      else
831
         time = trainp(1,step,1)
853
         time = trainp(1,step,1)
832
      endif
854
      endif
833
 
855
 
834
c     Write output to CF netCDF
856
c     Write output to CF netCDF
835
      cdfname  = outfile
857
      cdfname  = outfile
836
      
858
      
837
      varname  = 'COUNT'
859
      varname  = 'COUNT'
838
      longname = 'trajectory counts'
860
      longname = 'trajectory counts'
839
      varunit  = 'counts per grid point'
861
      varunit  = 'counts per grid point'
840
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
862
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
841
     >       clon,clat,nlonlat,dlonlat,cnt,time,dx,dy,xmin,ymin,nx,
863
     >       clon,clat,nlonlat,dlonlat,cnt,time,dx,dy,xmin,ymin,nx,
842
     >       ny,crefile,crefile,1)
864
     >       ny,crefile,crefile,1)
843
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
865
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
844
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
866
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
845
     >     ' [ time = ',time,' ]'    
867
     >     ' [ time = ',time,' ]'    
846
 
868
 
847
      varname  = 'RESIDENCE'
869
      varname  = 'RESIDENCE'
848
      longname = 'residence time'
870
      longname = 'residence time'
849
      varunit  = 'hours per grid point'
871
      varunit  = 'hours per grid point'
850
 
872
 
851
      print*,'crefile = ',crefile
873
      print*,'crefile = ',crefile
852
 
874
 
853
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
875
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
854
     >       clon,clat,nlonlat,dlonlat,res,time,dx,dy,xmin,ymin,nx,
876
     >       clon,clat,nlonlat,dlonlat,res,time,dx,dy,xmin,ymin,nx,
855
     >       ny,0,crefile,1)
877
     >       ny,0,crefile,1)
856
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
878
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
857
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
879
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
858
     >     ' [ time = ',time,' ]'    
880
     >     ' [ time = ',time,' ]'    
859
 
881
 
860
      varname  = 'AREA'
882
      varname  = 'AREA'
861
      longname = 'area corresponding to grid points'
883
      longname = 'area corresponding to grid points'
862
      varunit  = 'square kilometers'
884
      varunit  = 'square kilometers'
863
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
885
      call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
864
     >       clon,clat,nlonlat,dlonlat,area,time,dx,dy,xmin,ymin,nx,
886
     >       clon,clat,nlonlat,dlonlat,area,time,dx,dy,xmin,ymin,nx,
865
     >       ny,0,crefile,1)
887
     >       ny,0,crefile,1)
866
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
888
      write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
867
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
889
     >     '    ... ',trim(varname),' -> ',trim(cdfname),
868
     >     ' [ time = ',time,' ]'    
890
     >     ' [ time = ',time,' ]'    
869
      
891
      
870
      if ( field.ne.'nil' ) then
892
      if ( field.ne.'nil' ) then
871
         varname  = field
893
         varname  = field
872
         longname = field
894
         longname = field
873
         varunit  = 'as on trajectory file'
895
         varunit  = 'as on trajectory file'
874
         call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
896
         call  writecdf2D_cf (cdfname,varname,longname,varunit,gridtype,
875
     >       clon,clat,nlonlat,dlonlat,fld,time,dx,dy,xmin,ymin,nx,
897
     >       clon,clat,nlonlat,dlonlat,fld,time,dx,dy,xmin,ymin,nx,
876
     >       ny,0,crevar,1)
898
     >       ny,0,crevar,1)
877
 
899
 
878
         write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
900
         write(*,'(a8,a10,a5,a10,a10,f7.2,a2)') 
879
     >        '    ... ',trim(varname),' -> ',trim(cdfname),
901
     >        '    ... ',trim(varname),' -> ',trim(cdfname),
880
     >        ' [ time = ',time,' ]'    
902
     >        ' [ time = ',time,' ]'    
881
      endif
903
      endif
882
 
904
 
883
c     Write status information
905
c     Write status information
884
      print*
906
      print*
885
      print*,'              *** END OF PROGRAM DENSITY **'
907
      print*,'              *** END OF PROGRAM DENSITY **'
886
      print*,'========================================================='
908
      print*,'========================================================='
887
 
909
 
888
      end
910
      end
889
 
911
 
890
c     ********************************************************************
912
c     ********************************************************************
891
c     * GRIDDING SUBROUTINES                                             *
913
c     * GRIDDING SUBROUTINES                                             *
892
c     ********************************************************************
914
c     ********************************************************************
893
 
915
 
894
c     ---------------------------------------------------------------------
916
c     ---------------------------------------------------------------------
895
c     Gridding of one single data point (smoothing in km, deg, gridp)
917
c     Gridding of one single data point (smoothing in km, deg, gridp)
896
c     ---------------------------------------------------------------------
918
c     ---------------------------------------------------------------------
897
 
919
 
898
      subroutine gridding1 (lat,lon,addval,radius,unit,
920
      subroutine gridding1 (lat,lon,addval,radius,unit,
899
     >                      connect,connectval,
921
     >                      connect,connectval,
900
     >                      out,nx,ny,xmin,ymin,dx,dy)
922
     >                      out,nx,ny,xmin,ymin,dx,dy)
901
 
923
 
902
      implicit none
924
      implicit none
903
 
925
 
904
c     Declaration of subroutine parameters
926
c     Declaration of subroutine parameters
905
      real         lat,lon
927
      real         lat,lon
906
      integer      nx,ny
928
      integer      nx,ny
907
      real         xmin,ymin,dx,dy
929
      real         xmin,ymin,dx,dy
908
      real         out(nx,ny)
930
      real         out(nx,ny)
909
      real         radius
931
      real         radius
910
      character*80 unit
932
      character*80 unit
911
      integer      connectval
933
      integer      connectval
912
      integer      connect(nx,ny)
934
      integer      connect(nx,ny)
913
      real         addval
935
      real         addval
914
 
936
 
915
c     Auxiliary variables
937
c     Auxiliary variables
916
      integer   i,j,k
938
      integer   i,j,k
917
      integer   mu,md,nr,nl,n,m
939
      integer   mu,md,nr,nl,n,m
918
      integer   stackx(nx*ny),stacky(nx*ny)
940
      integer   stackx(nx*ny),stacky(nx*ny)
919
      integer   tab_x(nx*ny),tab_y(nx*ny)
941
      integer   tab_x(nx*ny),tab_y(nx*ny)
920
      real      tab_r(nx*ny)
942
      real      tab_r(nx*ny)
921
      integer   sp
943
      integer   sp
922
      real      lat2,lon2
944
      real      lat2,lon2
923
      real      dist,sum
945
      real      dist,sum
924
      real      xmax
946
      real      xmax
925
      integer   periodic
947
      integer   periodic
926
      integer   test
948
      integer   test
927
 
949
 
928
c     Numerical epsilon
950
c     Numerical epsilon
929
      real      eps
951
      real      eps
930
      parameter (eps=0.01)
952
      parameter (eps=0.01)
931
 
953
 
932
c     Externals
954
c     Externals
933
      real      sdis,weight
955
      real      sdis,weight
934
      external  sdis,weight
956
      external  sdis,weight
935
 
957
 
936
c     Check whether lat/lon point is valid
958
c     Check whether lat/lon point is valid
937
      xmax=xmin+real(nx-1)*dx
959
      xmax=xmin+real(nx-1)*dx
938
      if (lon.lt.xmin-eps) lon=lon+360.
960
      if (lon.lt.xmin-eps) lon=lon+360.
939
      if (lon.gt.xmax+eps) lon=lon-360.
961
      if (lon.gt.xmax+eps) lon=lon-360.
940
      if (abs(lat-90).lt.eps) lat=90.
962
      if (abs(lat-90).lt.eps) lat=90.
941
      if (abs(lat+90).lt.eps) lat=-90.
963
      if (abs(lat+90).lt.eps) lat=-90.
942
      if ((abs(lat).gt.(90.+eps)).or.
964
      if ((abs(lat).gt.(90.+eps)).or.
943
     >    (lon.lt.xmin-eps).or.(lon.gt.xmax+eps)) then
965
     >    (lon.lt.xmin-eps).or.(lon.gt.xmax+eps)) then
944
         print*,'Invalid lat/lon point ',lat,lon
966
         print*,'Invalid lat/lon point ',lat,lon
945
         return
967
         return
946
      endif
968
      endif
947
 
969
 
948
c     Set flag for periodic domain
970
c     Set flag for periodic domain
949
      if (abs(xmax-xmin-360.).lt.eps) then
971
      if (abs(xmax-xmin-360.).lt.eps) then
950
         periodic=1
972
         periodic=1
951
      else if (abs(xmax-xmin-360+dx).lt.eps) then
973
      else if (abs(xmax-xmin-360+dx).lt.eps) then
952
         periodic=2
974
         periodic=2
953
      else
975
      else
954
         periodic=0
976
         periodic=0
955
      endif
977
      endif
956
 
978
 
957
c     Get indices of one coarse grid point within search radius
979
c     Get indices of one coarse grid point within search radius
958
      i=nint((lon-xmin)/dx)+1
980
      i=nint((lon-xmin)/dx)+1
959
      if ((i.eq.nx).and.(periodic.eq.1)) i=1
981
      if ((i.eq.nx).and.(periodic.eq.1)) i=1
960
      j=nint((lat-ymin)/dy)+1
982
      j=nint((lat-ymin)/dy)+1
961
      lat2=ymin+real(j-1)*dy
983
      lat2=ymin+real(j-1)*dy
962
      lon2=xmin+real(i-1)*dx
984
      lon2=xmin+real(i-1)*dx
963
      dist=sdis(lon,lat,lon2,lat2,unit)
985
      dist=sdis(lon,lat,lon2,lat2,unit)
964
      if (dist.gt.radius) then
986
      if (dist.gt.radius) then
965
         print*,'1: Search radius is too small...'
987
         print*,'1: Search radius is too small...'
966
         stop
988
         stop
967
      endif
989
      endif
968
 
990
 
969
c     Get connected points
991
c     Get connected points
970
      k=0
992
      k=0
971
      stackx(1)=i
993
      stackx(1)=i
972
      stacky(1)=j
994
      stacky(1)=j
973
      sp=1
995
      sp=1
974
      do while (sp.ne.0) 
996
      do while (sp.ne.0) 
975
         
997
         
976
c        Get an element from stack
998
c        Get an element from stack
977
         n=stackx(sp)
999
         n=stackx(sp)
978
         m=stacky(sp)
1000
         m=stacky(sp)
979
         sp=sp-1
1001
         sp=sp-1
980
                  
1002
                  
981
c        Get distance from reference point
1003
c        Get distance from reference point
982
         lat2=ymin+real(m-1)*dy
1004
         lat2=ymin+real(m-1)*dy
983
         lon2=xmin+real(n-1)*dx
1005
         lon2=xmin+real(n-1)*dx
984
         dist=sdis(lon,lat,lon2,lat2,unit)
1006
         dist=sdis(lon,lat,lon2,lat2,unit)
985
 
1007
 
986
c        Check whether distance is smaller than search radius: connected
1008
c        Check whether distance is smaller than search radius: connected
987
         if (dist.lt.radius) then
1009
         if (dist.lt.radius) then
988
 
1010
 
989
c           Make entry in filter mask
1011
c           Make entry in filter mask
990
            k=k+1
1012
            k=k+1
991
            tab_x(k)=n
1013
            tab_x(k)=n
992
            tab_y(k)=m
1014
            tab_y(k)=m
993
            tab_r(k)=weight(dist,radius)
1015
            tab_r(k)=weight(dist,radius)
994
 
1016
 
995
c           Mark this point as visited
1017
c           Mark this point as visited
996
            connect(n,m)=connectval
1018
            connect(n,m)=connectval
997
                     
1019
                     
998
c           Get coordinates of neighbouring points
1020
c           Get coordinates of neighbouring points
999
            nr=n+1
1021
            nr=n+1
1000
            if ((nr.gt.nx)  .and.(periodic.eq.0)) nr=nx
1022
            if ((nr.gt.nx)  .and.(periodic.eq.0)) nr=nx
1001
            if ((nr.gt.nx-1).and.(periodic.eq.1)) nr=1
1023
            if ((nr.gt.nx-1).and.(periodic.eq.1)) nr=1
1002
            if ((nr.gt.nx)  .and.(periodic.eq.2)) nr=1
1024
            if ((nr.gt.nx)  .and.(periodic.eq.2)) nr=1
1003
            nl=n-1
1025
            nl=n-1
1004
            if ((nl.lt.1).and.(periodic.eq.0)) nl=1
1026
            if ((nl.lt.1).and.(periodic.eq.0)) nl=1
1005
            if ((nl.lt.1).and.(periodic.eq.1)) nl=nx-1
1027
            if ((nl.lt.1).and.(periodic.eq.1)) nl=nx-1
1006
            if ((nl.lt.1).and.(periodic.eq.2)) nl=nx
1028
            if ((nl.lt.1).and.(periodic.eq.2)) nl=nx
1007
            mu=m+1
1029
            mu=m+1
1008
            if (mu.gt.ny) mu=ny
1030
            if (mu.gt.ny) mu=ny
1009
            md=m-1
1031
            md=m-1
1010
            if (md.lt.1) md=1
1032
            if (md.lt.1) md=1
1011
 
1033
 
1012
c           Update stack
1034
c           Update stack
1013
            if (connect(nr,m).ne.connectval) then
1035
            if (connect(nr,m).ne.connectval) then
1014
               connect(nr,m)=connectval
1036
               connect(nr,m)=connectval
1015
               sp=sp+1
1037
               sp=sp+1
1016
               stackx(sp)=nr
1038
               stackx(sp)=nr
1017
               stacky(sp)=m
1039
               stacky(sp)=m
1018
            endif
1040
            endif
1019
            if (connect(nl,m).ne.connectval) then
1041
            if (connect(nl,m).ne.connectval) then
1020
               connect(nl,m)=connectval
1042
               connect(nl,m)=connectval
1021
               sp=sp+1
1043
               sp=sp+1
1022
               stackx(sp)=nl
1044
               stackx(sp)=nl
1023
               stacky(sp)=m
1045
               stacky(sp)=m
1024
            endif
1046
            endif
1025
            if (connect(n,mu).ne.connectval) then
1047
            if (connect(n,mu).ne.connectval) then
1026
               connect(n,mu)=connectval
1048
               connect(n,mu)=connectval
1027
               sp=sp+1
1049
               sp=sp+1
1028
               stackx(sp)=n
1050
               stackx(sp)=n
1029
               stacky(sp)=mu
1051
               stacky(sp)=mu
1030
            endif
1052
            endif
1031
            if (connect(n,md).ne.connectval) then
1053
            if (connect(n,md).ne.connectval) then
1032
               connect(n,md)=connectval
1054
               connect(n,md)=connectval
1033
               sp=sp+1
1055
               sp=sp+1
1034
               stackx(sp)=n
1056
               stackx(sp)=n
1035
               stacky(sp)=md
1057
               stacky(sp)=md
1036
            endif
1058
            endif
1037
         endif
1059
         endif
1038
         
1060
         
1039
      end do
1061
      end do
1040
 
1062
 
1041
      if (k.ge.1) then
1063
      if (k.ge.1) then
1042
         sum=0.
1064
         sum=0.
1043
         do i=1,k
1065
         do i=1,k
1044
            sum=sum+tab_r(i)
1066
            sum=sum+tab_r(i)
1045
         enddo
1067
         enddo
1046
         do i=1,k
1068
         do i=1,k
1047
            out(tab_x(i),tab_y(i))=out(tab_x(i),tab_y(i))+
1069
            out(tab_x(i),tab_y(i))=out(tab_x(i),tab_y(i))+
1048
     >                             addval*tab_r(i)/sum
1070
     >                             addval*tab_r(i)/sum
1049
 
1071
 
1050
            if ((tab_x(i).eq.1).and.(periodic.eq.1)) then
1072
            if ((tab_x(i).eq.1).and.(periodic.eq.1)) then
1051
               out(nx,tab_y(i))=out(nx,tab_y(i))+
1073
               out(nx,tab_y(i))=out(nx,tab_y(i))+
1052
     >                             addval*tab_r(i)/sum
1074
     >                             addval*tab_r(i)/sum
1053
            endif
1075
            endif
1054
         enddo
1076
         enddo
1055
      else
1077
      else
1056
         print*,'2: Search radius is too small...'
1078
         print*,'2: Search radius is too small...'
1057
         stop
1079
         stop
1058
      endif
1080
      endif
1059
 
1081
 
1060
      end
1082
      end
1061
 
1083
 
1062
 
1084
 
1063
c     ----------------------------------------------------------------------
1085
c     ----------------------------------------------------------------------
1064
c     Get spherical distance between lat/lon points
1086
c     Get spherical distance between lat/lon points
1065
c     ----------------------------------------------------------------------
1087
c     ----------------------------------------------------------------------
1066
            
1088
            
1067
      real function sdis(xp,yp,xq,yq,unit)
1089
      real function sdis(xp,yp,xq,yq,unit)
1068
 
1090
 
1069
c     Calculates spherical distance (in km) between two points given
1091
c     Calculates spherical distance (in km) between two points given
1070
c     by their spherical coordinates (xp,yp) and (xq,yq), respectively.
1092
c     by their spherical coordinates (xp,yp) and (xq,yq), respectively.
1071
 
1093
 
1072
      real         re
1094
      real         re
1073
      parameter    (re=6370.)
1095
      parameter    (re=6370.)
1074
      real         xp,yp,xq,yq,arg
1096
      real         xp,yp,xq,yq,arg
1075
      character*80 unit
1097
      character*80 unit
1076
      real         dlon
1098
      real         dlon
1077
 
1099
 
1078
      if ( unit.eq.'km' ) then
1100
      if ( unit.eq.'km' ) then
1079
 
1101
 
1080
         arg=sind(yp)*sind(yq)+cosd(yp)*cosd(yq)*cosd(xp-xq)
1102
         arg=sind(yp)*sind(yq)+cosd(yp)*cosd(yq)*cosd(xp-xq)
1081
         if (arg.lt.-1.) arg=-1.
1103
         if (arg.lt.-1.) arg=-1.
1082
         if (arg.gt.1.) arg=1.
1104
         if (arg.gt.1.) arg=1.
1083
         sdis=re*acos(arg)
1105
         sdis=re*acos(arg)
1084
         
1106
         
1085
      elseif ( unit.eq.'deg' ) then
1107
      elseif ( unit.eq.'deg' ) then
1086
 
1108
 
1087
         dlon = xp-xq
1109
         dlon = xp-xq
1088
         if ( dlon.gt. 180. ) dlon = dlon - 360.
1110
         if ( dlon.gt. 180. ) dlon = dlon - 360.
1089
         if ( dlon.lt.-180. ) dlon = dlon + 360.
1111
         if ( dlon.lt.-180. ) dlon = dlon + 360.
1090
         sdis = sqrt( dlon**2 + (yp-yq)**2 )
1112
         sdis = sqrt( dlon**2 + (yp-yq)**2 )
1091
 
1113
 
1092
      endif
1114
      endif
1093
      
1115
      
1094
 
1116
 
1095
c     Quick and dirty trick to avoid zero distances
1117
c     Quick and dirty trick to avoid zero distances
1096
      if (sdis.eq.0.) sdis=0.1
1118
      if (sdis.eq.0.) sdis=0.1
1097
 
1119
 
1098
      end
1120
      end
1099
 
1121
 
1100
c     ----------------------------------------------------------------------
1122
c     ----------------------------------------------------------------------
1101
c     Weight function for the filter mask
1123
c     Weight function for the filter mask
1102
c     ----------------------------------------------------------------------
1124
c     ----------------------------------------------------------------------
1103
 
1125
 
1104
      real function weight (r,radius)
1126
      real function weight (r,radius)
1105
 
1127
 
1106
c     Attribute to each distanc r its corresponding weight in the filter mask
1128
c     Attribute to each distanc r its corresponding weight in the filter mask
1107
 
1129
 
1108
      implicit none
1130
      implicit none
1109
 
1131
 
1110
c     Declaration of subroutine parameters
1132
c     Declaration of subroutine parameters
1111
      real r
1133
      real r
1112
      real radius
1134
      real radius
1113
 
1135
 
1114
c     Simple 0/1 mask
1136
c     Simple 0/1 mask
1115
      if (r.lt.radius) then
1137
      if (r.lt.radius) then
1116
         weight=exp(-r/radius)
1138
         weight=exp(-r/radius)
1117
      else
1139
      else
1118
         weight=0.
1140
         weight=0.
1119
      endif
1141
      endif
1120
 
1142
 
1121
      end
1143
      end
1122
 
1144
 
1123
 
1145
 
1124
c     ********************************************************************
1146
c     ********************************************************************
1125
c     * REPARAMETERIZATION SUBROUTINES                                   *
1147
c     * REPARAMETERIZATION SUBROUTINES                                   *
1126
c     ********************************************************************
1148
c     ********************************************************************
1127
 
1149
 
1128
c     -------------------------------------------------------------
1150
c     -------------------------------------------------------------
1129
c     Interpolation of the trajectory with a natural cubic spline
1151
c     Interpolation of the trajectory with a natural cubic spline
1130
c     -------------------------------------------------------------
1152
c     -------------------------------------------------------------
1131
 
1153
 
1132
      SUBROUTINE curvefit (time,lon,n,
1154
      SUBROUTINE curvefit (time,lon,n,
1133
     >                     sptime,splon,spn)
1155
     >                     sptime,splon,spn)
1134
 
1156
 
1135
c     Given the curve <time,lon> with <n> data points, fit a
1157
c     Given the curve <time,lon> with <n> data points, fit a
1136
c     cubic spline to this curve. The new curve is returned in 
1158
c     cubic spline to this curve. The new curve is returned in 
1137
c     <sptime,splon,spn> with <spn> data points. The parameter
1159
c     <sptime,splon,spn> with <spn> data points. The parameter
1138
c     <spn> specifies on entry the number of spline interpolated points
1160
c     <spn> specifies on entry the number of spline interpolated points
1139
c     along the curve.
1161
c     along the curve.
1140
      
1162
      
1141
      implicit none
1163
      implicit none
1142
 
1164
 
1143
c     Declaration of subroutine parameters
1165
c     Declaration of subroutine parameters
1144
      integer n
1166
      integer n
1145
      real time(n),lon(n)
1167
      real time(n),lon(n)
1146
      integer spn
1168
      integer spn
1147
      real sptime(spn),splon(spn)
1169
      real sptime(spn),splon(spn)
1148
 
1170
 
1149
c     Auxiliary variables
1171
c     Auxiliary variables
1150
      real y2ax(n)
1172
      real y2ax(n)
1151
      real dt
1173
      real dt
1152
      real s
1174
      real s
1153
      integer i
1175
      integer i
1154
      real order
1176
      real order
1155
 
1177
 
1156
c     Determine whether the input array is ascending or descending
1178
c     Determine whether the input array is ascending or descending
1157
      if (time(1).gt.time(n)) then
1179
      if (time(1).gt.time(n)) then
1158
         order=-1.
1180
         order=-1.
1159
      else
1181
      else
1160
         order= 1.
1182
         order= 1.
1161
      endif
1183
      endif
1162
 
1184
 
1163
c     Bring the time array into ascending order
1185
c     Bring the time array into ascending order
1164
      do i=1,n
1186
      do i=1,n
1165
         time(i)=order*time(i)
1187
         time(i)=order*time(i)
1166
      enddo
1188
      enddo
1167
 
1189
 
1168
c     Prepare the (natural) cubic spline interpolation
1190
c     Prepare the (natural) cubic spline interpolation
1169
      call spline (time,lon,n,1.e30,1.e30,y2ax)
1191
      call spline (time,lon,n,1.e30,1.e30,y2ax)
1170
      dt=(time(n)-time(1))/real(spn-1)
1192
      dt=(time(n)-time(1))/real(spn-1)
1171
      do i=1,spn
1193
      do i=1,spn
1172
         sptime(i)=time(1)+real(i-1)*dt
1194
         sptime(i)=time(1)+real(i-1)*dt
1173
      enddo
1195
      enddo
1174
      
1196
      
1175
c     Do the spline interpolation
1197
c     Do the spline interpolation
1176
      do i=1,spn
1198
      do i=1,spn
1177
         call splint(time,lon,y2ax,n,sptime(i),s)
1199
         call splint(time,lon,y2ax,n,sptime(i),s)
1178
         splon(i)=s
1200
         splon(i)=s
1179
      enddo
1201
      enddo
1180
 
1202
 
1181
c     Change the time arrays back
1203
c     Change the time arrays back
1182
      do i=1,spn
1204
      do i=1,spn
1183
         sptime(i)=order*sptime(i)
1205
         sptime(i)=order*sptime(i)
1184
      enddo
1206
      enddo
1185
      do i=1,n
1207
      do i=1,n
1186
         time(i)=order*time(i)
1208
         time(i)=order*time(i)
1187
      enddo
1209
      enddo
1188
 
1210
 
1189
      return
1211
      return
1190
      end
1212
      end
1191
 
1213
 
1192
c     -------------------------------------------------------------
1214
c     -------------------------------------------------------------
1193
c     Basic routines for spline interpolation (Numerical Recipes)
1215
c     Basic routines for spline interpolation (Numerical Recipes)
1194
c     -------------------------------------------------------------
1216
c     -------------------------------------------------------------
1195
 
1217
 
1196
      SUBROUTINE spline(x,y,n,yp1,ypn,y2)
1218
      SUBROUTINE spline(x,y,n,yp1,ypn,y2)
1197
      INTEGER n,NMAX
1219
      INTEGER n,NMAX
1198
      REAL yp1,ypn,x(n),y(n),y2(n)
1220
      REAL yp1,ypn,x(n),y(n),y2(n)
1199
      PARAMETER (NMAX=500)
1221
      PARAMETER (NMAX=500)
1200
      INTEGER i,k
1222
      INTEGER i,k
1201
      REAL p,qn,sig,un,u(NMAX)
1223
      REAL p,qn,sig,un,u(NMAX)
1202
      if (yp1.gt..99e30) then
1224
      if (yp1.gt..99e30) then
1203
        y2(1)=0.
1225
        y2(1)=0.
1204
        u(1)=0.
1226
        u(1)=0.
1205
      else
1227
      else
1206
        y2(1)=-0.5
1228
        y2(1)=-0.5
1207
        u(1)=(3./(x(2)-x(1)))*((y(2)-y(1))/(x(2)-x(1))-yp1)
1229
        u(1)=(3./(x(2)-x(1)))*((y(2)-y(1))/(x(2)-x(1))-yp1)
1208
      endif
1230
      endif
1209
      do 11 i=2,n-1
1231
      do 11 i=2,n-1
1210
        sig=(x(i)-x(i-1))/(x(i+1)-x(i-1))
1232
        sig=(x(i)-x(i-1))/(x(i+1)-x(i-1))
1211
        p=sig*y2(i-1)+2.
1233
        p=sig*y2(i-1)+2.
1212
        y2(i)=(sig-1.)/p
1234
        y2(i)=(sig-1.)/p
1213
        u(i)=(6.*((y(i+1)-y(i))/(x(i+
1235
        u(i)=(6.*((y(i+1)-y(i))/(x(i+
1214
     *1)-x(i))-(y(i)-y(i-1))/(x(i)-x(i-1)))/(x(i+1)-x(i-1))-sig*
1236
     *1)-x(i))-(y(i)-y(i-1))/(x(i)-x(i-1)))/(x(i+1)-x(i-1))-sig*
1215
     *u(i-1))/p
1237
     *u(i-1))/p
1216
11    continue
1238
11    continue
1217
      if (ypn.gt..99e30) then
1239
      if (ypn.gt..99e30) then
1218
        qn=0.
1240
        qn=0.
1219
        un=0.
1241
        un=0.
1220
      else
1242
      else
1221
        qn=0.5
1243
        qn=0.5
1222
        un=(3./(x(n)-x(n-1)))*(ypn-(y(n)-y(n-1))/(x(n)-x(n-1)))
1244
        un=(3./(x(n)-x(n-1)))*(ypn-(y(n)-y(n-1))/(x(n)-x(n-1)))
1223
      endif
1245
      endif
1224
      y2(n)=(un-qn*u(n-1))/(qn*y2(n-1)+1.)
1246
      y2(n)=(un-qn*u(n-1))/(qn*y2(n-1)+1.)
1225
      do 12 k=n-1,1,-1
1247
      do 12 k=n-1,1,-1
1226
        y2(k)=y2(k)*y2(k+1)+u(k)
1248
        y2(k)=y2(k)*y2(k+1)+u(k)
1227
12    continue
1249
12    continue
1228
      return
1250
      return
1229
      END
1251
      END
1230
 
1252
 
1231
      SUBROUTINE splint(xa,ya,y2a,n,x,y)
1253
      SUBROUTINE splint(xa,ya,y2a,n,x,y)
1232
      INTEGER n
1254
      INTEGER n
1233
      REAL x,y,xa(n),y2a(n),ya(n)
1255
      REAL x,y,xa(n),y2a(n),ya(n)
1234
      INTEGER k,khi,klo
1256
      INTEGER k,khi,klo
1235
      REAL a,b,h
1257
      REAL a,b,h
1236
      klo=1
1258
      klo=1
1237
      khi=n
1259
      khi=n
1238
1     if (khi-klo.gt.1) then
1260
1     if (khi-klo.gt.1) then
1239
        k=(khi+klo)/2
1261
        k=(khi+klo)/2
1240
        if(xa(k).gt.x)then
1262
        if(xa(k).gt.x)then
1241
          khi=k
1263
          khi=k
1242
        else
1264
        else
1243
          klo=k
1265
          klo=k
1244
        endif
1266
        endif
1245
      goto 1
1267
      goto 1
1246
      endif
1268
      endif
1247
      h=xa(khi)-xa(klo)
1269
      h=xa(khi)-xa(klo)
1248
      if (h.eq.0.) then
1270
      if (h.eq.0.) then
1249
         print*,'bad xa input in splint'
1271
         print*,'bad xa input in splint'
1250
         stop
1272
         stop
1251
      endif
1273
      endif
1252
      a=(xa(khi)-x)/h
1274
      a=(xa(khi)-x)/h
1253
      b=(x-xa(klo))/h
1275
      b=(x-xa(klo))/h
1254
      y=a*ya(klo)+b*ya(khi)+((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi))*(h**
1276
      y=a*ya(klo)+b*ya(khi)+((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi))*(h**
1255
     *2)/6.
1277
     *2)/6.
1256
      return
1278
      return
1257
      END
1279
      END
1258
 
1280
 
1259
c     ********************************************************************
1281
c     ********************************************************************
1260
c     * INPUT / OUTPUT SUBROUTINES                                       *
1282
c     * INPUT / OUTPUT SUBROUTINES                                       *
1261
c     ********************************************************************
1283
c     ********************************************************************
1262
 
1284
 
1263
 
1285
 
1264
c     --------------------------------------------------------------------
1286
c     --------------------------------------------------------------------
1265
c     Subroutines to write the CF netcdf output file
1287
c     Subroutines to write the CF netcdf output file
1266
c     --------------------------------------------------------------------
1288
c     --------------------------------------------------------------------
1267
 
1289
 
1268
      subroutine writecdf2D_cf 
1290
      subroutine writecdf2D_cf 
1269
     >          (cdfname,varname,longname,unit,gridtype,clon,clat,
1291
     >          (cdfname,varname,longname,unit,gridtype,clon,clat,
1270
     >           nlonlat,dlonlat,arr,time,dx,dy,xmin,ymin,nx,ny,
1292
     >           nlonlat,dlonlat,arr,time,dx,dy,xmin,ymin,nx,ny,
1271
     >           crefile,crevar,cretime)
1293
     >           crefile,crevar,cretime)
1272
 
1294
 
1273
c     Create and write to the CF netcdf file <cdfname>. The variable
1295
c     Create and write to the CF netcdf file <cdfname>. The variable
1274
c     with name <varname> and with time <time> is written. The data
1296
c     with name <varname> and with time <time> is written. The data
1275
c     are in the two-dimensional array <arr>. The list <dx,dy,xmin,
1297
c     are in the two-dimensional array <arr>. The list <dx,dy,xmin,
1276
c     ymin,nx,ny> specifies the output grid. The flags <crefile> and
1298
c     ymin,nx,ny> specifies the output grid. The flags <crefile> and
1277
c     <crevar> determine whether the file and/or the variable should
1299
c     <crevar> determine whether the file and/or the variable should
1278
c     be created; correspondingly for the unlimited dimension <time>
1300
c     be created; correspondingly for the unlimited dimension <time>
1279
c     with the flag <cretime>.
1301
c     with the flag <cretime>.
1280
 
1302
 
1281
      USE netcdf
1303
      USE netcdf
1282
 
1304
 
1283
      IMPLICIT NONE
1305
      IMPLICIT NONE
1284
 
1306
 
1285
c     Declaration of input parameters
1307
c     Declaration of input parameters
1286
      character*80 cdfname
1308
      character*80 cdfname
1287
      character*80 varname,longname,unit
1309
      character*80 varname,longname,unit
1288
      integer      nx,ny
1310
      integer      nx,ny
1289
      real         arr(nx,ny)
1311
      real         arr(nx,ny)
1290
      real         dx,dy,xmin,ymin
1312
      real         dx,dy,xmin,ymin
1291
      real         time
1313
      real         time
1292
      integer      crefile,crevar,cretime
1314
      integer      crefile,crevar,cretime
1293
      character*80 gridtype
1315
      character*80 gridtype
1294
      real         clon,clat
1316
      real         clon,clat
1295
      integer      nlonlat
1317
      integer      nlonlat
1296
      real         dlonlat
1318
      real         dlonlat
1297
 
1319
 
1298
c     Local variables
1320
c     Local variables
1299
      integer      ierr
1321
      integer      ierr
1300
      integer      ncID
1322
      integer      ncID
1301
      integer      LonDimId,    varLonID
1323
      integer      LonDimId,    varLonID
1302
      integer      LatDimID,    varLatID
1324
      integer      LatDimID,    varLatID
1303
      integer      TimeDimID,   varTimeID
1325
      integer      TimeDimID,   varTimeID
1304
      real         longitude(nx)
1326
      real         longitude(nx)
1305
      real         latitude (ny)
1327
      real         latitude (ny)
1306
      real         timeindex
1328
      real         timeindex
1307
      integer      i
1329
      integer      i
1308
      integer      nvars,varids(100)
1330
      integer      nvars,varids(100)
1309
      integer      ndims,dimids(100)
1331
      integer      ndims,dimids(100)
1310
      real         timelist(1000)
1332
      real         timelist(1000)
1311
      integer      ntimes
1333
      integer      ntimes
1312
      integer      ind
1334
      integer      ind
1313
      integer      varID
1335
      integer      varID
1314
 
1336
 
1315
c     Quick an dirty solution for fieldname conflict
1337
c     Quick an dirty solution for fieldname conflict
1316
      if ( varname.eq.'time' ) varname = 'TIME'
1338
      if ( varname.eq.'time' ) varname = 'TIME'
1317
 
1339
 
1318
c     Initially set error to indicate no errors.
1340
c     Initially set error to indicate no errors.
1319
      ierr = 0
1341
      ierr = 0
1320
 
1342
 
1321
c     ---- Create the netCDF - skip if <crefile=0> ----------------------
1343
c     ---- Create the netCDF - skip if <crefile=0> ----------------------
1322
      if ( crefile.ne.1 ) goto 100
1344
      if ( crefile.ne.1 ) goto 100
1323
 
1345
 
1324
c     Create the file 
1346
c     Create the file 
1325
      ierr = nf90_create(trim(cdfname), NF90_CLOBBER, ncID)
1347
      ierr = nf90_create(trim(cdfname), NF90_CLOBBER, ncID)
1326
      
1348
      
1327
c     Define dimensions 
1349
c     Define dimensions 
1328
      ierr=nf90_def_dim(ncID,'longitude',nx            , LonDimID )
1350
      ierr=nf90_def_dim(ncID,'longitude',nx            , LonDimID )
1329
      ierr=nf90_def_dim(ncID,'latitude' ,ny            , LatDimID )
1351
      ierr=nf90_def_dim(ncID,'latitude' ,ny            , LatDimID )
1330
      ierr=nf90_def_dim(ncID,'time'     ,nf90_unlimited, TimeDimID)
1352
      ierr=nf90_def_dim(ncID,'time'     ,nf90_unlimited, TimeDimID)
1331
      
1353
      
1332
c     Define coordinate Variables 
1354
c     Define coordinate Variables 
1333
      ierr = nf90_def_var(ncID,'longitude',NF90_FLOAT,
1355
      ierr = nf90_def_var(ncID,'longitude',NF90_FLOAT,
1334
     >     (/ LonDimID /),varLonID)
1356
     >     (/ LonDimID /),varLonID)
1335
      ierr = nf90_put_att(ncID, varLonID, "standard_name","longitude")
1357
      ierr = nf90_put_att(ncID, varLonID, "standard_name","longitude")
1336
      ierr = nf90_put_att(ncID, varLonID, "units"      ,"degree_east")
1358
      ierr = nf90_put_att(ncID, varLonID, "units"      ,"degree_east")
1337
      
1359
      
1338
      ierr = nf90_def_var(ncID,'latitude',NF90_FLOAT,
1360
      ierr = nf90_def_var(ncID,'latitude',NF90_FLOAT,
1339
     >     (/ LatDimID /),varLatID)
1361
     >     (/ LatDimID /),varLatID)
1340
      ierr = nf90_put_att(ncID, varLatID, "standard_name", "latitude")
1362
      ierr = nf90_put_att(ncID, varLatID, "standard_name", "latitude")
1341
      ierr = nf90_put_att(ncID, varLatID, "units"    ,"degree_north")
1363
      ierr = nf90_put_att(ncID, varLatID, "units"    ,"degree_north")
1342
      
1364
      
1343
      ierr = nf90_def_var(ncID,'time',NF90_FLOAT, 
1365
      ierr = nf90_def_var(ncID,'time',NF90_FLOAT, 
1344
     >     (/ TimeDimID /), varTimeID)
1366
     >     (/ TimeDimID /), varTimeID)
1345
      ierr = nf90_put_att(ncID, varTimeID, "axis",            "T")
1367
      ierr = nf90_put_att(ncID, varTimeID, "axis",            "T")
1346
      ierr = nf90_put_att(ncID, varTimeID, "calendar", "standard")
1368
      ierr = nf90_put_att(ncID, varTimeID, "calendar", "standard")
1347
      ierr = nf90_put_att(ncID, varTimeID, "long_name",    "time")
1369
      ierr = nf90_put_att(ncID, varTimeID, "long_name",    "time")
1348
      ierr = nf90_put_att(ncID, varTimeID, "units",       "hours")
1370
      ierr = nf90_put_att(ncID, varTimeID, "units",       "hours")
1349
      
1371
      
1350
c     Write global attributes 
1372
c     Write global attributes 
1351
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'Conventions', 'CF-1.0')
1373
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'Conventions', 'CF-1.0')
1352
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'title',  
1374
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'title',  
1353
     >     'Trajectory Densities')
1375
     >     'Trajectory Densities')
1354
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'source', 
1376
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'source', 
1355
     >     'Lagranto Trajectories')
1377
     >     'Lagranto Trajectories')
1356
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'institution', 
1378
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'institution', 
1357
     >     'ETH Zurich, IACETH')
1379
     >     'ETH Zurich, IACETH')
1358
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'grid',trim(gridtype) ) 
1380
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'grid',trim(gridtype) ) 
1359
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'clon',clon )
1381
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'clon',clon )
1360
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'clat',clat )
1382
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'clat',clat )
1361
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'nlonlat',nlonlat )
1383
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'nlonlat',nlonlat )
1362
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dlonlat',dlonlat )
1384
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dlonlat',dlonlat )
1363
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'nx',nx )
1385
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'nx',nx )
1364
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'ny',ny )
1386
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'ny',ny )
1365
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dx',dx )
1387
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dx',dx )
1366
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dy',dy )
1388
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'dy',dy )
1367
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'xmin',xmin )
1389
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'xmin',xmin )
1368
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'ymin',ymin )
1390
      ierr = nf90_put_att(ncID, NF90_GLOBAL, 'ymin',ymin )
1369
 
1391
 
1370
c     Write coordinate data 
1392
c     Write coordinate data 
1371
      do i = 1,nx+1
1393
      do i = 1,nx+1
1372
         longitude(i) = xmin + real(i-1) * dx
1394
         longitude(i) = xmin + real(i-1) * dx
1373
      enddo
1395
      enddo
1374
      do i = 1,ny+1
1396
      do i = 1,ny+1
1375
         latitude(i)  = ymin + real(i-1) * dy
1397
         latitude(i)  = ymin + real(i-1) * dy
1376
      enddo
1398
      enddo
1377
      
1399
      
1378
c     Check whether the definition was successful
1400
c     Check whether the definition was successful
1379
      ierr = nf90_enddef(ncID)
1401
      ierr = nf90_enddef(ncID)
1380
      if (ierr.gt.0) then
1402
      if (ierr.gt.0) then
1381
         print*, 'An error occurred while attempting to ', 
1403
         print*, 'An error occurred while attempting to ', 
1382
     >        'finish definition mode.'
1404
     >        'finish definition mode.'
1383
         stop
1405
         stop
1384
      endif
1406
      endif
1385
      
1407
      
1386
c     Write coordinate data  
1408
c     Write coordinate data  
1387
      ierr = nf90_put_var(ncID,varLonID ,longitude)
1409
      ierr = nf90_put_var(ncID,varLonID ,longitude)
1388
      ierr = nf90_put_var(ncID,varLatID ,latitude )
1410
      ierr = nf90_put_var(ncID,varLatID ,latitude )
1389
      
1411
      
1390
c     Close netCDF file 
1412
c     Close netCDF file 
1391
      ierr = nf90_close(ncID)
1413
      ierr = nf90_close(ncID)
1392
      
1414
      
1393
 100  continue
1415
 100  continue
1394
 
1416
 
1395
c     ---- Define a new variable - skip if <crevar=0> -----------------------
1417
c     ---- Define a new variable - skip if <crevar=0> -----------------------
1396
 
1418
 
1397
      if ( crevar.ne.1 ) goto 110
1419
      if ( crevar.ne.1 ) goto 110
1398
      
1420
      
1399
c     Open the file for read(write access
1421
c     Open the file for read(write access
1400
      ierr = nf90_open  (trim(cdfname), NF90_WRITE  , ncID)
1422
      ierr = nf90_open  (trim(cdfname), NF90_WRITE  , ncID)
1401
 
1423
 
1402
c     Get the IDs for dimensions
1424
c     Get the IDs for dimensions
1403
      ierr = nf90_inq_dimid(ncID,'longitude', LonDimID )
1425
      ierr = nf90_inq_dimid(ncID,'longitude', LonDimID )
1404
      ierr = nf90_inq_dimid(ncID,'latitude' , LatDimID )
1426
      ierr = nf90_inq_dimid(ncID,'latitude' , LatDimID )
1405
      ierr = nf90_inq_dimid(ncID,'time'     , TimeDimID)
1427
      ierr = nf90_inq_dimid(ncID,'time'     , TimeDimID)
1406
 
1428
 
1407
c     Enter define mode
1429
c     Enter define mode
1408
      ierr = nf90_redef(ncID)
1430
      ierr = nf90_redef(ncID)
1409
 
1431
 
1410
c     Write definition and add attributes
1432
c     Write definition and add attributes
1411
      ierr = nf90_def_var(ncID,varname,NF90_FLOAT,
1433
      ierr = nf90_def_var(ncID,varname,NF90_FLOAT,
1412
     >                   (/ LonDimID, LatDimID, TimeDimID /),varID)
1434
     >                   (/ LonDimID, LatDimID, TimeDimID /),varID)
1413
      ierr = nf90_put_att(ncID, varID, "long_name" , longname )
1435
      ierr = nf90_put_att(ncID, varID, "long_name" , longname )
1414
      ierr = nf90_put_att(ncID, varID, "units"     , unit     ) 
1436
      ierr = nf90_put_att(ncID, varID, "units"     , unit     ) 
1415
      ierr = nf90_put_att(ncID, varID, '_FillValue', -999.99  ) 
1437
      ierr = nf90_put_att(ncID, varID, '_FillValue', -999.99  ) 
1416
 
1438
 
1417
c     Check whether definition was successful
1439
c     Check whether definition was successful
1418
      ierr = nf90_enddef(ncID)
1440
      ierr = nf90_enddef(ncID)
1419
      if (ierr.gt.0) then
1441
      if (ierr.gt.0) then
1420
         print*, 'An error occurred while attempting to ', 
1442
         print*, 'An error occurred while attempting to ', 
1421
     >           'finish definition mode.'
1443
     >           'finish definition mode.'
1422
         stop
1444
         stop
1423
      endif
1445
      endif
1424
      print*,trim(varname),' defined on ',trim(cdfname)
1446
      print*,trim(varname),' defined on ',trim(cdfname)
1425
 
1447
 
1426
c     Close netCDF file 
1448
c     Close netCDF file 
1427
      ierr = nf90_close(ncID)
1449
      ierr = nf90_close(ncID)
1428
 
1450
 
1429
 110  continue
1451
 110  continue
1430
 
1452
 
1431
c     ---- Create a new time (unlimited dimension) - skip if <cretime=0> ------
1453
c     ---- Create a new time (unlimited dimension) - skip if <cretime=0> ------
1432
 
1454
 
1433
      if ( cretime.ne.1 ) goto 120
1455
      if ( cretime.ne.1 ) goto 120
1434
 
1456
 
1435
c     Open the file for read/write access
1457
c     Open the file for read/write access
1436
      ierr = nf90_open  (trim(cdfname), NF90_WRITE, ncID)
1458
      ierr = nf90_open  (trim(cdfname), NF90_WRITE, ncID)
1437
      
1459
      
1438
c     Get the list of times on the netCDF file
1460
c     Get the list of times on the netCDF file
1439
      ierr = nf90_inq_dimid(ncID,'time', TimeDimID)
1461
      ierr = nf90_inq_dimid(ncID,'time', TimeDimID)
1440
      if ( ierr.ne.0 ) then
1462
      if ( ierr.ne.0 ) then
1441
         print*,'Time dimension is not defined on ',trim(cdfname),
1463
         print*,'Time dimension is not defined on ',trim(cdfname),
1442
     >          ' .... Stop'
1464
     >          ' .... Stop'
1443
         stop
1465
         stop
1444
      endif
1466
      endif
1445
      ierr = nf90_inquire_dimension(ncID, TimeDimID, len = ntimes)
1467
      ierr = nf90_inquire_dimension(ncID, TimeDimID, len = ntimes)
1446
      ierr = nf90_inq_varid(ncID,'time', varTimeID)
1468
      ierr = nf90_inq_varid(ncID,'time', varTimeID)
1447
      if ( ierr.ne.0 ) then
1469
      if ( ierr.ne.0 ) then
1448
         print*,'Variable time is not defined on ',trim(cdfname),
1470
         print*,'Variable time is not defined on ',trim(cdfname),
1449
     >          ' ... Stop'
1471
     >          ' ... Stop'
1450
         stop
1472
         stop
1451
      endif
1473
      endif
1452
      ierr = nf90_get_var(ncID,varTimeID,timelist(1:ntimes))
1474
      ierr = nf90_get_var(ncID,varTimeID,timelist(1:ntimes))
1453
 
1475
 
1454
c     Decide whether a new time must be written
1476
c     Decide whether a new time must be written
1455
      ind = 0
1477
      ind = 0
1456
      do i=1,ntimes
1478
      do i=1,ntimes
1457
         if ( time.eq.timelist(i) ) ind = i
1479
         if ( time.eq.timelist(i) ) ind = i
1458
      enddo
1480
      enddo
1459
 
1481
 
1460
c     Extend the time list if required 
1482
c     Extend the time list if required 
1461
      if ( ind.eq.0 ) then
1483
      if ( ind.eq.0 ) then
1462
         ntimes           = ntimes + 1
1484
         ntimes           = ntimes + 1
1463
         timelist(ntimes) = time
1485
         timelist(ntimes) = time
1464
         ierr = nf90_put_var(ncID,varTimeID,timelist(1:ntimes))
1486
         ierr = nf90_put_var(ncID,varTimeID,timelist(1:ntimes))
1465
      endif
1487
      endif
1466
 
1488
 
1467
c     Close netCDF file 
1489
c     Close netCDF file 
1468
      ierr = nf90_close(ncID)
1490
      ierr = nf90_close(ncID)
1469
 
1491
 
1470
 120  continue
1492
 120  continue
1471
 
1493
 
1472
c     ---- Write data --------------------------------------------------
1494
c     ---- Write data --------------------------------------------------
1473
 
1495
 
1474
c     Open the file for read/write access
1496
c     Open the file for read/write access
1475
      ierr = nf90_open  (trim(cdfname), NF90_WRITE , ncID)
1497
      ierr = nf90_open  (trim(cdfname), NF90_WRITE , ncID)
1476
 
1498
 
1477
c     Get the varID
1499
c     Get the varID
1478
      ierr = nf90_inq_varid(ncID,varname, varID )
1500
      ierr = nf90_inq_varid(ncID,varname, varID )
1479
      if (ierr.ne.0) then
1501
      if (ierr.ne.0) then
1480
         print*,'Variable ',trim(varname),' is not defined on ',
1502
         print*,'Variable ',trim(varname),' is not defined on ',
1481
     >          trim(cdfname)
1503
     >          trim(cdfname)
1482
         stop
1504
         stop
1483
      endif
1505
      endif
1484
 
1506
 
1485
c     Get the time index
1507
c     Get the time index
1486
      ierr = nf90_inq_dimid(ncID,'time', TimeDimID)
1508
      ierr = nf90_inq_dimid(ncID,'time', TimeDimID)
1487
      if ( ierr.ne.0 ) then
1509
      if ( ierr.ne.0 ) then
1488
         print*,'Time dimension is not defined on ',trim(cdfname),
1510
         print*,'Time dimension is not defined on ',trim(cdfname),
1489
     >          ' .... Stop'
1511
     >          ' .... Stop'
1490
         stop
1512
         stop
1491
      endif
1513
      endif
1492
      ierr = nf90_inquire_dimension(ncID, TimeDimID, len = ntimes)
1514
      ierr = nf90_inquire_dimension(ncID, TimeDimID, len = ntimes)
1493
      ierr = nf90_inq_varid(ncID,'time', varTimeID)
1515
      ierr = nf90_inq_varid(ncID,'time', varTimeID)
1494
      if ( ierr.ne.0 ) then
1516
      if ( ierr.ne.0 ) then
1495
         print*,'Variable time is not defined on ',trim(cdfname),
1517
         print*,'Variable time is not defined on ',trim(cdfname),
1496
     >          ' ... Stop'
1518
     >          ' ... Stop'
1497
         stop
1519
         stop
1498
      endif
1520
      endif
1499
      ierr = nf90_get_var(ncID,varTimeID,timelist(1:ntimes))
1521
      ierr = nf90_get_var(ncID,varTimeID,timelist(1:ntimes))
1500
      ind = 0
1522
      ind = 0
1501
      do i=1,ntimes
1523
      do i=1,ntimes
1502
         if ( time.eq.timelist(i) ) ind = i
1524
         if ( time.eq.timelist(i) ) ind = i
1503
      enddo
1525
      enddo
1504
      if (ind.eq.0) then
1526
      if (ind.eq.0) then
1505
         print*,'Time',time,' is not defined on the netCDF file',
1527
         print*,'Time',time,' is not defined on the netCDF file',
1506
     >          trim(cdfname),' ... Stop'
1528
     >          trim(cdfname),' ... Stop'
1507
         stop
1529
         stop
1508
      endif
1530
      endif
1509
 
1531
 
1510
c     Write data block      
1532
c     Write data block      
1511
      ierr = nf90_put_var(ncID,varID,arr,
1533
      ierr = nf90_put_var(ncID,varID,arr,
1512
     >                    start = (/ 1, 1, ind /), 
1534
     >                    start = (/ 1, 1, ind /), 
1513
     >                    count = (/ nx, ny, 1 /) )
1535
     >                    count = (/ nx, ny, 1 /) )
1514
 
1536
 
1515
c     Check whether writing was successful 
1537
c     Check whether writing was successful 
1516
      ierr = nf90_close(ncID)
1538
      ierr = nf90_close(ncID)
1517
      if (ierr.ne.0) then
1539
      if (ierr.ne.0) then
1518
         write(*,*) trim(nf90_strerror(ierr))
1540
         write(*,*) trim(nf90_strerror(ierr))
1519
         write(*,*) 'An error occurred while attempting to ', 
1541
         write(*,*) 'An error occurred while attempting to ', 
1520
     >              'close the netcdf file.'
1542
     >              'close the netcdf file.'
1521
         write(*,*) 'in clscdf_CF'
1543
         write(*,*) 'in clscdf_CF'
1522
      endif
1544
      endif
1523
 
1545
 
1524
      end
1546
      end
1525
 
1547
 
1526
 
1548
 
1527
c     ********************************************************************************
1549
c     ********************************************************************************
1528
c     * Transformation routine: LMSTOLM and PHSTOPH from library gm2em               *
1550
c     * Transformation routine: LMSTOLM and PHSTOPH from library gm2em               *
1529
c     ********************************************************************************
1551
c     ********************************************************************************
1530
 
1552
 
1531
      REAL FUNCTION LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1553
      REAL FUNCTION LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1532
C
1554
C
1533
C**** LMSTOLM  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1555
C**** LMSTOLM  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1534
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1556
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1535
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1557
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1536
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1558
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1537
C**   AUFRUF   :   LAM = LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1559
C**   AUFRUF   :   LAM = LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
1538
C**   ENTRIES  :   KEINE
1560
C**   ENTRIES  :   KEINE
1539
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1561
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
1540
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1562
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1541
C**                IM ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1563
C**                IM ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1542
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1564
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1543
C**   VERSIONS-
1565
C**   VERSIONS-
1544
C**   DATUM    :   03.05.90
1566
C**   DATUM    :   03.05.90
1545
C**
1567
C**
1546
C**   EXTERNALS:   KEINE
1568
C**   EXTERNALS:   KEINE
1547
C**   EINGABE-
1569
C**   EINGABE-
1548
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1570
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1549
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1571
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1550
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1572
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1551
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1573
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1552
C**   AUSGABE-
1574
C**   AUSGABE-
1553
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1575
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1554
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1576
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1555
C**
1577
C**
1556
C**   COMMON-
1578
C**   COMMON-
1557
C**   BLOECKE  :   KEINE
1579
C**   BLOECKE  :   KEINE
1558
C**
1580
C**
1559
C**   FEHLERBE-
1581
C**   FEHLERBE-
1560
C**   HANDLUNG :   KEINE
1582
C**   HANDLUNG :   KEINE
1561
C**   VERFASSER:   D.MAJEWSKI
1583
C**   VERFASSER:   D.MAJEWSKI
1562
 
1584
 
1563
      REAL        LAMS,PHIS,POLPHI,POLLAM
1585
      REAL        LAMS,PHIS,POLPHI,POLLAM
1564
 
1586
 
1565
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1587
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1566
 
1588
 
1567
      ZSINPOL = SIN(ZPIR18*POLPHI)
1589
      ZSINPOL = SIN(ZPIR18*POLPHI)
1568
      ZCOSPOL = COS(ZPIR18*POLPHI)
1590
      ZCOSPOL = COS(ZPIR18*POLPHI)
1569
      ZLAMPOL = ZPIR18*POLLAM
1591
      ZLAMPOL = ZPIR18*POLLAM
1570
      ZPHIS   = ZPIR18*PHIS
1592
      ZPHIS   = ZPIR18*PHIS
1571
      ZLAMS   = LAMS
1593
      ZLAMS   = LAMS
1572
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1594
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1573
      ZLAMS   = ZPIR18*ZLAMS
1595
      ZLAMS   = ZPIR18*ZLAMS
1574
 
1596
 
1575
      ZARG1   = SIN(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1597
      ZARG1   = SIN(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1576
     1                          ZCOSPOL*           SIN(ZPHIS)) -
1598
     1                          ZCOSPOL*           SIN(ZPHIS)) -
1577
     2          COS(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1599
     2          COS(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1578
      ZARG2   = COS(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1600
      ZARG2   = COS(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  +
1579
     1                          ZCOSPOL*           SIN(ZPHIS)) +
1601
     1                          ZCOSPOL*           SIN(ZPHIS)) +
1580
     2          SIN(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1602
     2          SIN(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
1581
      IF (ABS(ZARG2).LT.1.E-30) THEN
1603
      IF (ABS(ZARG2).LT.1.E-30) THEN
1582
        IF (ABS(ZARG1).LT.1.E-30) THEN
1604
        IF (ABS(ZARG1).LT.1.E-30) THEN
1583
          LMSTOLM =   0.0
1605
          LMSTOLM =   0.0
1584
        ELSEIF (ZARG1.GT.0.) THEN
1606
        ELSEIF (ZARG1.GT.0.) THEN
1585
              LMSTOLAM =  90.0
1607
              LMSTOLAM =  90.0
1586
            ELSE
1608
            ELSE
1587
              LMSTOLAM = -90.0
1609
              LMSTOLAM = -90.0
1588
            ENDIF
1610
            ENDIF
1589
      ELSE
1611
      ELSE
1590
        LMSTOLM = ZRPI18*ATAN2(ZARG1,ZARG2)
1612
        LMSTOLM = ZRPI18*ATAN2(ZARG1,ZARG2)
1591
      ENDIF
1613
      ENDIF
1592
 
1614
 
1593
      RETURN
1615
      RETURN
1594
      END
1616
      END
1595
 
1617
 
1596
 
1618
 
1597
      REAL FUNCTION PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1619
      REAL FUNCTION PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1598
C
1620
C
1599
C**** PHSTOPH  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1621
C**** PHSTOPH  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1600
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1622
C****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1601
C****                 ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1623
C****                 ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1602
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1624
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1603
C**   AUFRUF   :   PHI = PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1625
C**   AUFRUF   :   PHI = PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
1604
C**   ENTRIES  :   KEINE
1626
C**   ENTRIES  :   KEINE
1605
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1627
C**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
1606
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1628
C**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1607
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1629
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1608
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1630
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1609
C**   VERSIONS-
1631
C**   VERSIONS-
1610
C**   DATUM    :   03.05.90
1632
C**   DATUM    :   03.05.90
1611
C**
1633
C**
1612
C**   EXTERNALS:   KEINE
1634
C**   EXTERNALS:   KEINE
1613
C**   EINGABE-
1635
C**   EINGABE-
1614
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1636
C**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
1615
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1637
C**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
1616
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1638
C**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
1617
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1639
C**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
1618
C**   AUSGABE-
1640
C**   AUSGABE-
1619
C**   PARAMETER:   WAHRE GEOGRAPHISCHE BREITE ALS WERT DER FUNKTION
1641
C**   PARAMETER:   WAHRE GEOGRAPHISCHE BREITE ALS WERT DER FUNKTION
1620
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1642
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1621
C**
1643
C**
1622
C**   COMMON-
1644
C**   COMMON-
1623
C**   BLOECKE  :   KEINE
1645
C**   BLOECKE  :   KEINE
1624
C**
1646
C**
1625
C**   FEHLERBE-
1647
C**   FEHLERBE-
1626
C**   HANDLUNG :   KEINE
1648
C**   HANDLUNG :   KEINE
1627
C**   VERFASSER:   D.MAJEWSKI
1649
C**   VERFASSER:   D.MAJEWSKI
1628
 
1650
 
1629
      REAL        LAMS,PHIS,POLPHI,POLLAM
1651
      REAL        LAMS,PHIS,POLPHI,POLLAM
1630
 
1652
 
1631
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1653
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1632
 
1654
 
1633
      SINPOL = SIN(ZPIR18*POLPHI)
1655
      SINPOL = SIN(ZPIR18*POLPHI)
1634
      COSPOL = COS(ZPIR18*POLPHI)
1656
      COSPOL = COS(ZPIR18*POLPHI)
1635
      ZPHIS  = ZPIR18*PHIS
1657
      ZPHIS  = ZPIR18*PHIS
1636
      ZLAMS  = LAMS
1658
      ZLAMS  = LAMS
1637
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1659
      IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
1638
      ZLAMS  = ZPIR18*ZLAMS
1660
      ZLAMS  = ZPIR18*ZLAMS
1639
      ARG     = COSPOL*COS(ZPHIS)*COS(ZLAMS) + SINPOL*SIN(ZPHIS)
1661
      ARG     = COSPOL*COS(ZPHIS)*COS(ZLAMS) + SINPOL*SIN(ZPHIS)
1640
 
1662
 
1641
      PHSTOPH = ZRPI18*ASIN(ARG)
1663
      PHSTOPH = ZRPI18*ASIN(ARG)
1642
 
1664
 
1643
      RETURN
1665
      RETURN
1644
      END
1666
      END
1645
 
1667
 
1646
 
1668
 
1647
      REAL FUNCTION LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1669
      REAL FUNCTION LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1648
C
1670
C
1649
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1671
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1650
C
1672
C
1651
C**** LMTOLMS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM
1673
C**** LMTOLMS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM
1652
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1674
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1653
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1675
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1654
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1676
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1655
C**   AUFRUF   :   LAM = LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1677
C**   AUFRUF   :   LAM = LMTOLMS (PHI, LAM, POLPHI, POLLAM)
1656
C**   ENTRIES  :   KEINE
1678
C**   ENTRIES  :   KEINE
1657
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM AUF
1679
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM AUF
1658
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1680
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1659
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1681
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1660
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1682
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1661
C**   VERSIONS-
1683
C**   VERSIONS-
1662
C**   DATUM    :   03.05.90
1684
C**   DATUM    :   03.05.90
1663
C**
1685
C**
1664
C**   EXTERNALS:   KEINE
1686
C**   EXTERNALS:   KEINE
1665
C**   EINGABE-
1687
C**   EINGABE-
1666
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1688
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1667
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1689
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1668
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1690
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1669
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1691
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1670
C**   AUSGABE-
1692
C**   AUSGABE-
1671
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1693
C**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
1672
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1694
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1673
C**
1695
C**
1674
C**   COMMON-
1696
C**   COMMON-
1675
C**   BLOECKE  :   KEINE
1697
C**   BLOECKE  :   KEINE
1676
C**
1698
C**
1677
C**   FEHLERBE-
1699
C**   FEHLERBE-
1678
C**   HANDLUNG :   KEINE
1700
C**   HANDLUNG :   KEINE
1679
C**   VERFASSER:   G. DE MORSIER
1701
C**   VERFASSER:   G. DE MORSIER
1680
 
1702
 
1681
      REAL        LAM,PHI,POLPHI,POLLAM
1703
      REAL        LAM,PHI,POLPHI,POLLAM
1682
 
1704
 
1683
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1705
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1684
 
1706
 
1685
      ZSINPOL = SIN(ZPIR18*POLPHI)
1707
      ZSINPOL = SIN(ZPIR18*POLPHI)
1686
      ZCOSPOL = COS(ZPIR18*POLPHI)
1708
      ZCOSPOL = COS(ZPIR18*POLPHI)
1687
      ZLAMPOL =     ZPIR18*POLLAM
1709
      ZLAMPOL =     ZPIR18*POLLAM
1688
      ZPHI    =     ZPIR18*PHI
1710
      ZPHI    =     ZPIR18*PHI
1689
      ZLAM    = LAM
1711
      ZLAM    = LAM
1690
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1712
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1691
      ZLAM    = ZPIR18*ZLAM
1713
      ZLAM    = ZPIR18*ZLAM
1692
 
1714
 
1693
      ZARG1   = - SIN(ZLAM-ZLAMPOL)*COS(ZPHI)
1715
      ZARG1   = - SIN(ZLAM-ZLAMPOL)*COS(ZPHI)
1694
      ZARG2   = - ZSINPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL)+ZCOSPOL*SIN(ZPHI)
1716
      ZARG2   = - ZSINPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL)+ZCOSPOL*SIN(ZPHI)
1695
      IF (ABS(ZARG2).LT.1.E-30) THEN
1717
      IF (ABS(ZARG2).LT.1.E-30) THEN
1696
        IF (ABS(ZARG1).LT.1.E-30) THEN
1718
        IF (ABS(ZARG1).LT.1.E-30) THEN
1697
          LMTOLMS =   0.0
1719
          LMTOLMS =   0.0
1698
        ELSEIF (ZARG1.GT.0.) THEN
1720
        ELSEIF (ZARG1.GT.0.) THEN
1699
              LMTOLMS =  90.0
1721
              LMTOLMS =  90.0
1700
            ELSE
1722
            ELSE
1701
              LMTOLMS = -90.0
1723
              LMTOLMS = -90.0
1702
            ENDIF
1724
            ENDIF
1703
      ELSE
1725
      ELSE
1704
        LMTOLMS = ZRPI18*ATAN2(ZARG1,ZARG2)
1726
        LMTOLMS = ZRPI18*ATAN2(ZARG1,ZARG2)
1705
      ENDIF
1727
      ENDIF
1706
 
1728
 
1707
      RETURN
1729
      RETURN
1708
      END
1730
      END
1709
 
1731
 
1710
 
1732
 
1711
      REAL FUNCTION PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1733
      REAL FUNCTION PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1712
C
1734
C
1713
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1735
C%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
1714
C
1736
C
1715
C**** PHTOPHS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI
1737
C**** PHTOPHS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI
1716
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1738
C****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
1717
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1739
C****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
1718
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1740
C****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1719
C**   AUFRUF   :   PHI = PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1741
C**   AUFRUF   :   PHI = PHTOPHS (PHI, LAM, POLPHI, POLLAM)
1720
C**   ENTRIES  :   KEINE
1742
C**   ENTRIES  :   KEINE
1721
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI AUF
1743
C**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI AUF
1722
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1744
C**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
1723
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1745
C**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
1724
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1746
C**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
1725
C**   VERSIONS-
1747
C**   VERSIONS-
1726
C**   DATUM    :   03.05.90
1748
C**   DATUM    :   03.05.90
1727
C**
1749
C**
1728
C**   EXTERNALS:   KEINE
1750
C**   EXTERNALS:   KEINE
1729
C**   EINGABE-
1751
C**   EINGABE-
1730
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1752
C**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
1731
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1753
C**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
1732
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1754
C**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
1733
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1755
C**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
1734
C**   AUSGABE-
1756
C**   AUSGABE-
1735
C**   PARAMETER:   ROTIERTE BREITE PHIS ALS WERT DER FUNKTION
1757
C**   PARAMETER:   ROTIERTE BREITE PHIS ALS WERT DER FUNKTION
1736
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1758
C**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
1737
C**
1759
C**
1738
C**   COMMON-
1760
C**   COMMON-
1739
C**   BLOECKE  :   KEINE
1761
C**   BLOECKE  :   KEINE
1740
C**
1762
C**
1741
C**   FEHLERBE-
1763
C**   FEHLERBE-
1742
C**   HANDLUNG :   KEINE
1764
C**   HANDLUNG :   KEINE
1743
C**   VERFASSER:   G. DE MORSIER
1765
C**   VERFASSER:   G. DE MORSIER
1744
 
1766
 
1745
      REAL        LAM,PHI,POLPHI,POLLAM
1767
      REAL        LAM,PHI,POLPHI,POLLAM
1746
 
1768
 
1747
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1769
      DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
1748
 
1770
 
1749
      ZSINPOL = SIN(ZPIR18*POLPHI)
1771
      ZSINPOL = SIN(ZPIR18*POLPHI)
1750
      ZCOSPOL = COS(ZPIR18*POLPHI)
1772
      ZCOSPOL = COS(ZPIR18*POLPHI)
1751
      ZLAMPOL = ZPIR18*POLLAM
1773
      ZLAMPOL = ZPIR18*POLLAM
1752
      ZPHI    = ZPIR18*PHI
1774
      ZPHI    = ZPIR18*PHI
1753
      ZLAM    = LAM
1775
      ZLAM    = LAM
1754
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1776
      IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
1755
      ZLAM    = ZPIR18*ZLAM
1777
      ZLAM    = ZPIR18*ZLAM
1756
      ZARG    = ZCOSPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL) + ZSINPOL*SIN(ZPHI)
1778
      ZARG    = ZCOSPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL) + ZSINPOL*SIN(ZPHI)
1757
 
1779
 
1758
      PHTOPHS = ZRPI18*ASIN(ZARG)
1780
      PHTOPHS = ZRPI18*ASIN(ZARG)
1759
 
1781
 
1760
      RETURN
1782
      RETURN
1761
      END
1783
      END
1762
 
1784
 
1763
c     ------------------------------------------------------------------
1785
c     ------------------------------------------------------------------
1764
c     Compute Cos/Sin of an argument in Degree instead of Radian
1786
c     Compute Cos/Sin of an argument in Degree instead of Radian
1765
c     ------------------------------------------------------------------
1787
c     ------------------------------------------------------------------
1766
 
1788
 
1767
      real function cosd(arg)
1789
      real function cosd(arg)
1768
 
1790
 
1769
      real,intent(IN) :: arg
1791
      real,intent(IN) :: arg
1770
      real,parameter :: grad2rad=3.1415926/360.
1792
      real,parameter :: grad2rad=3.1415926/360.
1771
      cosd=cos(arg*grad2rad)
1793
      cosd=cos(arg*grad2rad)
1772
      return
1794
      return
1773
      end
1795
      end
1774
 
1796
 
1775
      real function sind(arg)
1797
      real function sind(arg)
1776
 
1798
 
1777
      real,intent(IN) :: arg
1799
      real,intent(IN) :: arg
1778
      real,parameter :: grad2rad=3.1415926/360.
1800
      real,parameter :: grad2rad=3.1415926/360.
1779
      sind=sin(arg*grad2rad)
1801
      sind=sin(arg*grad2rad)
1780
      return
1802
      return
1781
      end
1803
      end
1782
 
1804
 
1783
 
1805