OB.DAAC Logo
NASA Logo
Ocean Color Science Software

ocssw V2022
interp_hycom_ascii.f
Go to the documentation of this file.
1  program interp_hycom
2 
3  use netcdf
4  USE hdf5
5 c
6 c This program interpolate a global 1/12 degree hycom temperature
7 c or salinity field at selected depth into a regular grid of
8 c a quarter degree (1440x720).
9 c
10 c This program is based on isubaregion.f written by Alan J. Wallcraft
11 c It takes two pre-generated NetCDF files: hycom_weight.nc
12 c that stores the interpolation weight table from the hycom grid
13 c to the regular grid based on a bilinear interpolation
14 c The weight table was generated using a modified program based
15 c on isuba_gmapi.f also written by Wallcraft.
16 c
17 c The second file is mask1.nc. It provides the landmask for the
18 c output grid. This two files have to reside in the directory
19 c where the program is executed.
20 c
21 c The input file is a NetCDF file extracted from the HYCOM output
22 c file via their OpenDAP server. The variable field contains only
23 c one depth only. If you change the input file format, you will
24 c have to modify the code to read it properly.
25 c
26 c The output file is a NetCDF file containing 1D arrays for latitude
27 c and longitude, two 3D arrays for temp and salt. There are
28 c 9 pre-defined depth at 0, 10, 20, 30, 50, 100, 250, 500, 1000 meter
29 c below the sea surface.
30 c
31 c Original Author:
32 c Alan J. Wallcraft, NRL, January 2005 and January 2009.c
33 c Modified by
34 c Peggy Li, JPL, August 31, 2010
35 c Modified by
36 c Joel Gales, GSFC, September 5, 2010
37 c Add HDF5 and binary output
38 c
39 c
40  character*40 :: field, timetag, depth, varname
41  character*128 :: dir_in, dir_out
42  character*256 :: file_in, file_out
43  integer :: nargs,iargc
44  integer :: level
45  integer :: idm, jdm,idm_out,jdm_out,ddim
46  integer :: i,ii,ip,j,jj,jp
47  integer :: if_sm,il_sm,jf_sm,jl_sm
48  integer :: status,ncid,ncid2,vid
49  integer :: latid, lonid, depthid
50  integer :: varid, xoutid, youtid
51  real, allocatable :: lats(:), lons(:), dep(:)
52  character*80 :: attstr
53  integer :: start_3d(4),count_3d(4)
54 ! logical :: lmask
55  integer, allocatable :: m_sm(:,:), iv_sm(:,:)
56  integer, allocatable :: m_out(:,:), m_osm(:,:)
57  real, allocatable :: a_in(:,:)
58  real, allocatable, target :: a_out(:,:)
59 c
60  integer, allocatable :: i_out(:,:),j_out(:,:)
61  real, allocatable :: x_out(:,:),y_out(:,:)
62 c
63  real, parameter :: spval=2.0**100 ! spval
64  real, parameter :: hspval=0.5*2.0**100 ! half spval
65 ! DOUBLE PRECISION :: time
66  logical :: file_exists
67  integer :: count, count1
68 
69  INTEGER(HID_T) :: file_id
70  INTEGER(HID_T) :: dset_id
71  INTEGER :: rank
72  INTEGER(HSIZE_T), DIMENSION(2) :: dims_sal
73  INTEGER(HSIZE_T), DIMENSION(3) :: offset=(/0,0,0/)
74  INTEGER(HID_T) :: filespace
75  INTEGER(HID_T) :: dataspace
76  real(4), POINTER :: pt
77  real(4) xx
78 
79  integer slash_pos
80  CHARACTER datadir*255
81 
82  include "aquarius.fin"
83 c
84 c define input/output dimension
85 c parse input arguments
86  idm=4500;jdm=3298
87  idm_out=1440;jdm_out=720
88  nargs=iargc()
89  if (nargs.eq.2) then
90 ! call getarg(1,field)
91 ! call getarg(2,timetag)
92 ! call getarg(2,depth)
93  call getarg(1,file_in)
94  call getarg(2,dir_out)
95  else
96  print *,
97 ! & "Command:get_hycom [temp|salt] yyyymmdd depth infile outdir"
98  & "Command:get_hycom [temp|salt] infile outdir"
99 ! print *," depth: 0,10,20,30,50,100,250,500,and 1000"
100 ! stop
101  call exit(1)
102  endif
103  field = 'salt'
104  depth = '0'
105 
106  slash_pos = index(file_in,'/',back=.true.)
107  timetag = file_in(slash_pos+7:slash_pos+10)//file_in(slash_pos+12:slash_pos+14)
108 
109  if (field .eq. "temp") then
110  varname="temperature"
111  elseif (field .eq. "salt") then
112  varname="salinity"
113  else
114  print *, "field has to be either temp or salt"
115 ! stop
116  call exit(1)
117  endif
118  level = -1
119  if (depth .eq. '0') level=1
120  if (depth .eq. '10') level=2
121  if (depth .eq. '20') level=3
122  if (depth .eq. '30') level=4
123  if (depth .eq. '50') level=5
124  if (depth .eq. '100') level=6
125  if (depth .eq. '250') level=7
126  if (depth .eq. '500') level=8
127  if (depth .eq. '1000') level=9
128  if (level < 0) then
129  print *, "depth value is invalid"
130 ! stop
131  call exit(1)
132  endif
133 
134  allocate( iv_sm(jdm,2) )
135 c
136  allocate( m_sm(idm,jdm), m_osm(idm_out,jdm_out) )
137  allocate( m_out(idm_out,jdm_out) )
138  allocate( a_in(idm,jdm), a_out(idm_out,jdm_out) )
139 c
140  allocate( i_out(idm_out,jdm_out), j_out(idm_out,jdm_out) )
141  allocate( x_out(idm_out,jdm_out), y_out(idm_out,jdm_out) )
142 
143  a_out(:,:)=spval
144 ! write(*,*) 'interpolating ',trim(file_in),' to ',
145 ! & trim(file_out)
146 
147  call getenv('OCDATAROOT', datadir)
148 
149 c readin the land mask for the output grid
150  status=nf90_open(trim(datadir)//'/aquarius/static/hycom_landmask.nc', 0, ncid)
151  if (status /= nf90_noerr) then
152  write(*,*) 'Land mask "hycom_landmask.nc" cannot be opened.'
153  call handle_err(status)
154  endif
155 
156  status=nf90_inq_varid(ncid,"mask",vid)
157  if (status /= nf90_noerr) then
158  call handle_err(status)
159  endif
160 
161  status=nf90_get_var(ncid,vid,m_out)
162  if (status /= nf90_noerr) then
163  call handle_err(status)
164  endif
165 
166  status=nf90_close(ncid)
167 
168 
169 c stop if input file does not exit
170 c and create the output file if not exist
171  inquire(file=file_in, exist=file_exists)
172  if (.not. file_exists) then
173  print *, file_in, " does not exist"
174 ! stop
175  call exit(1)
176  endif
177 ! inquire(FILE=file_out, EXIST=file_exists)
178 ! if (.not. file_exists) then
179 
180  file_out=trim(dir_out)//'/N'//trim(timetag)//'00_SALINITY_HYCOM_24h.nc'
181 
182 ! print *, "Create ",trim(file_out)
183  ddim = 9
184 
185  status=nf90_create(file_out,0, ncid)
186  if (status /= nf90_noerr) then
187  write(*,*) 'NetCDF output file cannot be created.'
188  call handle_err(status)
189  endif
190 
191  status=nf90_def_dim(ncid,'lat', jdm_out, latid)
192  if (status /= nf90_noerr) call handle_err(status)
193  status=nf90_def_dim(ncid,'lon', idm_out, lonid)
194  if (status /= nf90_noerr) call handle_err(status)
195 
196  status=nf90_def_var(ncid, 'salt', nf90_float,
197  & (/lonid,latid/), varid)
198  if (status /= nf90_noerr) call handle_err(status)
199  attstr="Salinity"
200  status=nf90_put_att(ncid,varid,'long_name',attstr)
201  attstr="PS"
202  status=nf90_put_att(ncid,varid,'units',attstr)
203  if (status /= nf90_noerr) call handle_err(status)
204  status=nf90_put_att(ncid,varid,'_FillValue',spval)
205  if (status /= nf90_noerr) call handle_err(status)
206  status=nf90_enddef(ncid)
207  if (status /= nf90_noerr) call handle_err(status)
208 
209  allocate(lats(jdm_out), lons(idm_out), dep(ddim))
210 
211  do i=1,idm_out
212  lons(i)=-180.125+i*0.25
213  enddo
214  do i=1,jdm_out
215  lats(i)=-90.125+i*0.25
216  enddo
217  dep(1)=0; dep(2)=10; dep(3)=20; dep(4)=30
218  dep(5)=50; dep(6)=100; dep(7)=250; dep(8)=500
219  dep(9)=1000
220 
221  deallocate(lats,lons,dep)
222 
223 
224 c Open input file and read in the field
225  open(10,file=file_in,form ='FORMATTED')
226 
227  do j=1,jdm
228  do i=1,idm
229  read (10,*) a_in(i,j)
230 ! write(*,*) a_in(i,j)
231  enddo
232  enddo
233  close(10)
234 
235  count = 0
236  do j= 1,jdm
237  do i= 1,idm
238  if (a_in(i,j).gt.hspval) then
239  count = count+1
240  m_sm(i,j) = 0
241  else
242  m_sm(i,j) = 1
243  endif
244  enddo
245  enddo
246  print *, "hspval", hspval
247  print *, "Input data ", count, " land point"
248 
249 c read in the weight file and output mask
250 
251  status=nf90_open(trim(datadir)//'/aquarius/static/hycom_weight.nc',0, ncid)
252 
253  if (status /= nf90_noerr) then
254  write(*,*) 'HYCOM weight file "hycom_weight.nc" cannot be opened.'
255  call handle_err(status)
256  endif
257 
258  status=nf90_inq_varid(ncid, 'x_out', xoutid)
259  if (status /= nf90_noerr) call handle_err(status)
260  status=nf90_inq_varid(ncid, 'y_out', youtid)
261  if (status /= nf90_noerr) call handle_err(status)
262  status=nf90_get_var(ncid,xoutid,x_out)
263  if (status /= nf90_noerr) call handle_err(status)
264  status=nf90_get_var(ncid,youtid,y_out)
265  if (status /= nf90_noerr) call handle_err(status)
266  status=nf90_close(ncid)
267  if (status /= nf90_noerr) call handle_err(status)
268 
269 c m_out(:,:)=1
270  do jj= 1,jdm_out
271  do ii= 1,idm_out
272  if (x_out(ii,jj).lt.hspval) then
273  i_out(ii,jj) = int(x_out(ii,jj))
274  x_out(ii,jj) = x_out(ii,jj) - i_out(ii,jj)
275  j_out(ii,jj) = int(y_out(ii,jj))
276  y_out(ii,jj) = y_out(ii,jj) - j_out(ii,jj)
277  else !update output mask???
278  m_out(ii,jj) = 0
279  endif
280  enddo !ii
281  enddo !jj
282 c
283 c --- form the p-grid smoother mask,
284 c --- set to 2 if a land point is needed for interpolation.
285 c --- we are assuming that "2" is never needed outside the
286 c --- target subregion, which will be the case unless the
287 c --- subregion rectangle is poorly chosen.
288 c
289 
290  count = 0
291  do jj= 1,jdm_out
292  do ii= 1,idm_out
293  count = 0
294  if (m_out(ii,jj).eq.1) then
295  j = j_out(ii,jj)
296  i = i_out(ii,jj)
297  jp = min(j+1,jdm)
298  if (i.ne.idm) then
299  ip = i+1
300  else !lperiod
301  ip = 1
302  endif
303  if (m_sm(i,j).eq.0) then
304  count = count+1
305  m_sm(i, j ) = 2
306  endif
307  if (m_sm(i,jp).eq.0) then
308  count = count+1
309  m_sm(i, jp) = 2
310  endif
311  if (m_sm(ip,j).eq.0) then
312  count = count+1
313  m_sm(ip,j) = 2
314  endif
315  if (m_sm(ip,jp).eq.0) then
316  count = count+1
317  m_sm(ip,jp) = 2
318  endif
319  if (count > 0) count1=count1+1
320  endif !sea-point
321  enddo !ii
322  enddo !jj
323 c
324  print *, "Total ", count1, "ocean point hits land"
325 
326  do j= 1,jdm
327  iv_sm(j,1) = idm
328  do i= 1,idm
329  if (m_sm(i,j).eq.2) then
330  iv_sm(j,1) = i
331  exit
332  endif
333  enddo
334  iv_sm(j,2) = 1
335  do i= idm,iv_sm(j,1),-1
336  if (m_sm(i,j).eq.2) then
337  iv_sm(j,2) = i
338  exit
339  endif
340  enddo
341  enddo
342  jf_sm = jdm
343  do j= 1,jdm
344  if (iv_sm(j,1).le.iv_sm(j,2)) then
345  jf_sm = j
346  exit
347  endif
348  enddo
349  jl_sm = 1
350  do j= jdm,jf_sm,-1
351  if (iv_sm(j,1).le.iv_sm(j,2)) then
352  jl_sm = j
353  exit
354  endif
355  enddo
356  if_sm = minval(iv_sm(:,1))
357  il_sm = maxval(iv_sm(:,2))
358 
359  call landfill( a_in,m_sm,idm, jdm,
360  & iv_sm,if_sm,il_sm,jf_sm,jl_sm)
361  call bilinear_p(a_in, idm, jdm,
362  & a_out, idm_out,jdm_out,
363  & m_sm, m_out,i_out,j_out,x_out,y_out)
364 
365 
366 c output the interpolated field
367  status = nf90_open(file_out,nf90_write,ncid2)
368  if (status /= nf90_noerr) call handle_err(status)
369  start_3d(1)=1
370  start_3d(2)=1
371  start_3d(3)=level
372  count_3d(1)=idm_out
373  count_3d(2)=jdm_out
374  count_3d(3)=1
375  status=nf90_inq_varid(ncid2,field,vid)
376  if (status /= nf90_noerr) call handle_err(status)
377  status=nf90_put_var(ncid2, vid,a_out,
378  & start=start_3d,count=count_3d)
379  if (status /= nf90_noerr) call handle_err(status)
380  status=nf90_close(ncid2)
381  if (status /= nf90_noerr) call handle_err(status)
382 
383 
384 c write out a land mask based on the output
385  do j=1,jdm_out
386  do i=1,idm_out
387  if (a_out(i,j) .eq. spval) then
388  m_out(i,j)=0
389  else
390  m_out(i,j)=1
391  endif
392  enddo
393  enddo
394 
395 C Write out HD5 file
396  file_out=trim(dir_out)//'/N'//trim(timetag)//'00_SALINITY_HYCOM_24h.h5'
397 
398  call create_hdf5(file_out, file_id)
399 
400  rank = 2
401  dims_sal(1) = 360*4
402  dims_sal(2) = 180*4
403 
404  call create_hdf5_real(file_id, 'salinity', rank, dims_sal, dset_id)
405  call set_space_hdf5(dset_id, rank, dims_sal, filespace, dataspace)
406  pt => a_out(1,1)
407  call write_hdf5_real(dset_id, filespace, dataspace, offset, dims_sal, pt)
408  call close_hdf5_ds(dset_id, dataspace, filespace)
409  call close_hdf5_df(file_id)
410 
411 
412 C Write binary file
413  file_out=trim(dir_out)//'/N'//trim(timetag)//'00_SALINITY_HYCOM_24h.dat'
414  open(unit=8,file=file_out, form='UNFORMATTED')
415  write(8) a_out
416  close(8)
417 
418  deallocate(iv_sm, m_sm, m_osm, m_out, a_in, a_out)
419  deallocate(i_out, j_out, x_out, y_out)
420 
421  write(*,*) ' '
422  write(*,*) 'NETCDF=N'//trim(timetag)//'00_SALINITY_HYCOM_24h.nc'
423  write(*,*) 'HDF5 =N'//trim(timetag)//'00_SALINITY_HYCOM_24h.h5'
424  write(*,*) 'BINARY=N'//trim(timetag)//'00_SALINITY_HYCOM_24h.dat'
425 
426  end program interp_hycom
427 
428  subroutine bilinear_p(a_in, idm_in, jdm_in,
429  & a_out,idm_out,jdm_out,
430  & m_in, m_out,i_out,j_out,x_out,y_out)
431  implicit none
432 c
433  integer idm_in, jdm_in,
434  & idm_out,jdm_out
435  integer m_out(idm_out,jdm_out),
436  & m_in(idm_in,jdm_in),
437  & i_out(idm_out,jdm_out),
438  & j_out(idm_out,jdm_out)
439  real a_in( idm_in, jdm_in ),
440  & a_out(idm_out,jdm_out),
441  & x_out(idm_out,jdm_out),
442  & y_out(idm_out,jdm_out)
443 c
444 c --- interpolate from a_in to a_out.
445 c
446  integer i,ii,ip,j,jj,jp
447  integer ki,kj,iii,jjj
448  real sa, ss
449  real sx,sy
450  integer count
451  real s(-1:1, -1:1)
452  data s / 1.0, 2.0, 1.0,
453  & 2.0, 4.0, 2.0,
454  & 1.0, 2.0, 1.0 /
455  real, parameter :: spval=2.0**100 ! spval
456 
457 c
458  count = 0
459  do jj= 1,jdm_out
460  do ii= 1,idm_out
461  if (m_out(ii,jj).eq.1) then
462  count = count+1
463  sx = x_out(ii,jj)
464  sy = y_out(ii,jj)
465  i = i_out(ii,jj)
466  if (i.ne.idm_in) then
467  ip = i+1
468  else
469  ip = 1
470  endif
471  j = j_out(ii,jj)
472  jp = j+1
473 c
474 c doing a 3x3 interpolation for jj<552
475  if (jj<552) then
476  sa = 0.0
477  ss = 0.0
478  do kj= -1,1
479  jjj = j+kj
480  if (jjj==0) jjj=1
481  if (jjj>jdm_in) jjj=jdm_in
482  do ki= -1,1
483  iii = i+ki
484  if (iii==0) iii=idm_in
485  if (iii>idm_in) iii=1
486  if (m_in(iii,jjj).eq.1) then
487  sa = sa + s(ki,kj)*a_in(iii,jjj)
488  ss = ss + s(ki,kj)
489  endif
490  enddo
491  enddo
492  if (ss.ne.0.0) then
493 c
494 c at least one ocean point within stencil.
495 c
496  a_out( ii,jj) = sa/ss
497  else
498  a_out(ii,jj) = spval
499  endif
500  else
501  a_out(ii,jj) = (1.0-sx)*(1.0-sy)*a_in(i, j ) +
502  & (1.0-sx)* sy *a_in(i, jp) +
503  & sx *(1.0-sy)*a_in(ip,j ) +
504  & sx * sy *a_in(ip,jp)
505 * if (a_out(ii,jj).lt.0.0) then
506 * write(6,'(a,6i5,2f7.3,5f9.2)')
507 * & 'ii,jj,i,ip,j,jp,sx,sy,a_out,a_in',
508 * & ii,jj,i,ip,j,jp,
509 * & sx,sy,a_out(ii,jj),
510 * & a_in(i, j ),
511 * & a_in(i, jp),
512 * & a_in(ip,j ),
513 * & a_in(ip,jp)
514 * endif
515  endif
516  endif
517  enddo
518  enddo
519  print *, "Output ocean point:", count
520  return
521  end
522 
523  subroutine landfill(a,mask,m,n, iv,if,il,jf,jl)
524  implicit none
525 c
526  integer m,n,mask(m,n), iv(n,2),if,il,jf,jl
527  real a(m,n)
528 c
529 c --- extrapolate a 1-grid cell into the land mask,
530 c --- mask == 0 for land.
531 c --- mask == 1 for ocean.
532 c --- mask == 2 for land to be extrapolated to ocean.
533 c
534  integer, allocatable :: mm(:,:,:)
535 c
536  integer i,ii,ip0,ip1,ipass,j,jj,ki,kj,nleft,nup
537  real sa,ss
538 c
539  logical lfirst
540 c real s(-1:1,-1:1)
541  real s(-2:2,-2:2)
542  save lfirst,s
543 c
544  data lfirst / .true. /
545 c data s / 1.0, 2.0, 1.0,
546 c & 2.0, 4.0, 2.0,
547 c & 1.0, 2.0, 1.0 /
548  data s /1.0, 1.5, 2.0, 1.5, 1.0,
549  & 1.5, 2.0, 3.0, 2.0, 1.5,
550  & 2.0, 3.0, 4.0, 3.0, 2.0,
551  & 1.5, 2.0, 3.0, 2.0, 1.5,
552  & 1.0, 1.5, 2.0, 1.5, 1.0 /
553 c
554 c adding a halo to mm simplifies ocean selection logic.
555 c
556  allocate( mm(0:m+1,0:n+1,0:1) )
557 c
558  mm( : , : ,0) = 0
559  mm(1:m,1:n,0) = mask
560  mm( : , : ,1) = mm(:,:,0)
561 c
562 c --- repeated passes of 9-point "smoother" to
563 c --- convert all mask==2 points to mask==1.
564 c --- double-buffering mm allows in-place use of a.
565 c
566  if (lfirst) then
567  write(6,'(/a,6i5/)')
568  & 'landfill - m,n,if,il,jf,jl =',m,n,if,il,jf,jl
569  endif
570  do ipass= 1,n+m
571  ip0 = mod(ipass+1,2)
572  ip1 = mod(ipass, 2)
573  nup = 0
574  nleft = 0
575  do j= jf,jl
576  do i= iv(j,1),iv(j,2)
577  if (mm(i,j,ip0).eq.2) then
578  sa = 0.0
579  ss = 0.0
580  do kj= -2,2
581  jj = j+kj
582  do ki= -2,2
583  ii = i+ki
584  if ((ii>0) .and. (ii.le.m) .and. (jj>0)
585  & .and. (jj.le.n)) then
586  if (mm(ii,jj,ip0).eq.1) then
587  sa = sa + s(ki,kj)*a(ii,jj)
588  ss = ss + s(ki,kj)
589  endif
590  endif
591  enddo
592  enddo
593  if (ss.ne.0.0) then
594 c
595 c at least one ocean point within stencil.
596 c
597  a( i,j) = sa/ss
598  mm(i,j,ip1) = 1
599  nup = nup + 1
600 * if (mask(i,j).eq.1) then
601 * write(6,*) 'error - i,j,ip0,ip1,mask,mm = ',
602 * & i,j,ip0,ip1,mask(i,j),mm(i,j,ip0)
603 * stop
604 * endif
605 * if (mod(nup,1000).eq.1) then
606 * write(6,'(a,2i5,f5.1,f10.3)')
607 * & ' i,j,ss,a = ',i,j,ss,a(i,j)
608 * endif
609  else
610  nleft = nleft + 1
611  endif
612  endif
613  enddo
614  enddo
615  if (lfirst) then
616  write(6,'(a,i4,a,i6,a,i6,a)')
617  & 'landfill: pass',ipass,
618  & ' filled in',nup,
619  & ' points, with',nleft,' still to fill'
620  call flush(6)
621  endif
622  if (nup.eq.0) then
623  exit
624  endif
625  mm(if:il,jf:jl,ip0) = mm(if:il,jf:jl,ip1)
626  enddo ! ipass=1,...
627  if (lfirst) then
628  write(6,*)
629  lfirst = .false.
630  endif
631  if (nleft.ne.0) then
632  write(6,'(/a,i6,a/a/)')
633  & 'error in landfill - ',
634  & nleft,' "mask==2" values are not fillable',
635  & 'probably a mismatch between input and output land masks'
636  call flush(6)
637 c do j= jf,jl
638 c do i= iv(j,1),iv(j,2)
639 c if (mm(i,j,ip1).eq.2) then
640 c write(6,'(a,2i5)') 'mask==2 at (input) i,j = ',i,j
641 c endif
642 c enddo
643 c enddo
644 c write(6,*)
645 c call flush(6)
646 c stop
647  endif
648 c
649  mask=mm(1:m,1:n,ip1)
650  deallocate( mm )
651 c
652  return
653  end subroutine landfill
654 
655  subroutine psmooth(a,mask,amn,amx,m,n)
656  implicit none
657 c
658  integer m,n,mask(m,n)
659  real a(m,n),amn(m,n),amx(m,n)
660 c
661 c --- smooth under mask and within amn,amx range.
662 c
663  integer, allocatable :: mm(:,:)
664  real, allocatable :: aa(:,:)
665 c
666  integer i,ii,j,jj,ki,kj
667  real rss,sa
668 c
669  real s(-1:1,-1:1)
670  save s
671  data s / 1.0, 2.0, 1.0,
672  & 2.0, 4.0, 2.0,
673  & 1.0, 2.0, 1.0 /
674 c
675  rss = 1.0/sum(s(:,:))
676 c
677 c local copy of a.
678 c
679  allocate( aa(m,n) )
680  aa = a
681 c
682 c adding a halo to mm simplifies ocean selection logic.
683 c
684  allocate( mm(0:m+1,0:n+1) )
685  mm( 0, : ) = 0
686  mm(m+1, : ) = 0
687  mm( : , 0) = 0
688  mm( : ,n+1) = 0
689  mm(1:m,1:n) = mask
690 c
691  do j= 1,n
692  do i= 1,m
693  if (mm(i,j).eq.1) then
694  sa = 0.0
695  do kj= -1,1
696  jj = j+kj
697  do ki= -1,1
698  ii = i+ki
699  if (mm(ii,jj).eq.1) then
700  sa = sa + s(ki,kj)*aa(ii,jj) ! must use local copy of a
701  else
702  sa = sa + s(ki,kj)*aa(i ,j )
703  endif
704  enddo
705  enddo
706  a(i,j) = max( amn(i,j),
707  & min( amx(i,j), sa*rss ) )
708  endif
709  enddo
710  enddo
711 c
712  deallocate( aa, mm )
713 c
714  return
715  end subroutine psmooth
716 
717 c
718  subroutine handle_err(status)
719  integer :: status
720  print *, "NetCDF return error ", status
721 ! stop "Stopped"
722  call exit(1)
723  end subroutine handle_err
724 
725 
an array had not been initialized Several spelling and grammar corrections were which is read from the appropriate MCF the above metadata values were hard coded A problem calculating the average background DN for SWIR bands when the moon is in the space view port was corrected The new algorithm used to calculate the average background DN for all reflective bands when the moon is in the space view port is now the same as the algorithm employed by the thermal bands For non SWIR changes in the averages are typically less than Also for non SWIR the black body DNs remain a backup in case the SV DNs are not available For SWIR the changes in computed averages were larger because the old which used the black body suffered from contamination by the micron leak As a consequence of the if SV DNs are not available for the SWIR the EV pixels will not be the granule time is used to identify the appropriate tables within the set given for one LUT the first two or last two tables respectively will be used for the interpolation If there is only one LUT in the set of it will be treated as a constant LUT The manner in which Earth View data is checked for saturation was changed Previously the raw Earth View DNs and Space View DNs were checked against the lookup table values contained in the table dn_sat The change made is to check the raw Earth and Space View DNs to be sure they are less than the maximum saturation value and to check the Space View subtracted Earth View dns against a set of values contained in the new lookup table dn_sat_ev The metadata configuration and ASSOCIATEDINSTRUMENTSHORTNAME from the MOD02HKM product The same metatdata with extensions and were removed from the MOD021KM and MOD02OBC products ASSOCIATEDSENSORSHORTNAME was set to MODIS in all products These changes are reflected in new File Specification which users may consult for exact the pow functions were eliminated in Emissive_Cal and Emissive bands replaced by more efficient code Other calculations throughout the code were also made more efficient Aside from a few round off there was no difference to the product The CPU time decreased by about for a day case and for a night case A minor bug in calculating the uncertainty index for emissive bands was corrected The frame index(0-based) was previously being used the frame number(1-based) should have been used. There were only a few minor changes to the uncertainty index(maximum of 1 digit). 3. Some inefficient arrays(Sigma_RVS_norm_sq) were eliminated and some code lines in Preprocess_L1A_Data were moved into Process_OBCEng_Emiss. There were no changes to the product. Required RAM was reduced by 20 MB. Now
#define max(A, B)
Definition: main_biosmap.c:61
program interp_hycom
Definition: interp_hycom.f:1
subroutine handle_err(status)
Definition: interp_hycom.f:716
string & trim(string &s, const string &delimiters)
Definition: EnvsatUtil.cpp:29
#define min(A, B)
Definition: main_biosmap.c:62
subroutine landfill(a, mask, m, n, iv, if, il, jf, jl)
Definition: interp_hycom.f:521
subroutine bilinear_p(a_in, idm_in, jdm_in, a_out, idm_out, jdm_out, m_in, m_out, i_out, j_out, x_out, y_out)
Definition: interp_hycom.f:428
subroutine psmooth(a, mask, amn, amx, m, n)
Definition: interp_hycom.f:653