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
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)
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(:,:)
60 integer,
allocatable :: i_out(:,:),j_out(:,:)
61 real,
allocatable :: x_out(:,:),y_out(:,:)
63 real,
parameter :: spval=2.0**100
64 real,
parameter :: hspval=0.5*2.0**100
66 logical :: file_exists
67 integer :: count, count1
69 INTEGER(HID_T) :: file_id
70 INTEGER(HID_T) :: dset_id
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
82 include
"aquarius.fin"
87 idm_out=1440;jdm_out=720
93 call getarg(1,file_in)
94 call getarg(2,dir_out)
98 &
"Command:get_hycom [temp|salt] infile outdir"
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
109 if (field .eq.
"temp")
then
110 varname=
"temperature"
111 elseif (field .eq.
"salt")
then
114 print *,
"field has to be either temp or salt"
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
129 print *,
"depth value is invalid"
134 allocate( iv_sm(jdm,2) )
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) )
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) )
147 call getenv(
'OCDATAROOT', datadir)
150 status=nf90_open(
trim(datadir)//
'/aquarius/static/hycom_landmask.nc'
151 if (status /= nf90_noerr)
then
152 write(*,*)
'Land mask "hycom_landmask.nc" cannot be opened.'
156 status=nf90_inq_varid(ncid,
"mask",vid)
157 if (status /= nf90_noerr)
then
161 status=nf90_get_var(ncid,vid,m_out)
162 if (status /= nf90_noerr)
then
166 status=nf90_close(ncid)
171 inquire(file=file_in, exist=file_exists)
172 if (.not. file_exists)
then
173 print *, file_in,
" does not exist"
180 file_out=
trim(dir_out)//
'/N'//
trim(timetag)//
'00_SALINITY_HYCOM_24h.nc'
185 status=nf90_create(file_out,0, ncid)
186 if (status /= nf90_noerr)
then
187 write(*,*)
'NetCDF output file cannot be created.'
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)
196 status=nf90_def_var(ncid,
'salt', nf90_float,
197 & (/lonid,latid/), varid)
198 if (status /= nf90_noerr)
call handle_err(status)
200 status=nf90_put_att(ncid,varid,
'long_name',attstr)
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)
209 allocate(lats(jdm_out), lons(idm_out), dep(ddim))
212 lons(i)=-180.125+i*0.25
215 lats(i)=-90.125+i*0.25
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
221 deallocate(lats,lons,dep)
225 open(10,file=file_in,form =
'FORMATTED')
229 read (10,*) a_in(i,j)
238 if (a_in(i,j).gt.hspval)
then
246 print *,
"hspval", hspval
247 print *,
"Input data ", count,
" land point"
251 status=nf90_open(
trim(datadir)//
'/aquarius/static/hycom_weight.nc'
253 if (status /= nf90_noerr)
then
254 write(*,*)
'HYCOM weight file "hycom_weight.nc" cannot be opened.'
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)
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)
294 if (m_out(ii,jj).eq.1)
then
303 if (m_sm(i,j).eq.0)
then
307 if (m_sm(i,jp).eq.0)
then
311 if (m_sm(ip,j).eq.0)
then
315 if (m_sm(ip,jp).eq.0)
then
319 if (count > 0) count1=count1+1
324 print *,
"Total ", count1,
"ocean point hits land"
329 if (m_sm(i,j).eq.2)
then
335 do i= idm,iv_sm(j,1),-1
336 if (m_sm(i,j).eq.2)
then
344 if (iv_sm(j,1).le.iv_sm(j,2))
then
351 if (iv_sm(j,1).le.iv_sm(j,2))
then
356 if_sm = minval(iv_sm(:,1))
357 il_sm = maxval(iv_sm(:,2))
360 & iv_sm,if_sm,il_sm,jf_sm,jl_sm)
362 & a_out, idm_out,jdm_out,
363 & m_sm, m_out,i_out,j_out,x_out,y_out)
367 status = nf90_open(file_out,nf90_write,ncid2)
368 if (status /= nf90_noerr)
call handle_err(status)
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)
387 if (a_out(i,j) .eq. spval)
then
396 file_out=
trim(dir_out)//
'/N'//
trim(timetag)//
'00_SALINITY_HYCOM_24h.h5'
398 call create_hdf5(file_out, file_id)
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)
407 call write_hdf5_real(dset_id, filespace, dataspace, offset, dims_sal
408 call close_hdf5_ds(dset_id, dataspace, filespace)
409 call close_hdf5_df(file_id)
413 file_out=
trim(dir_out)//
'/N'//
trim(timetag)//
'00_SALINITY_HYCOM_24h.dat'
414 open(unit=8,file=file_out, form=
'UNFORMATTED')
418 deallocate(iv_sm, m_sm, m_osm, m_out, a_in, a_out)
419 deallocate(i_out, j_out, x_out, y_out)
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'
429 & a_out,idm_out,jdm_out,
430 & m_in, m_out,i_out,j_out,x_out,y_out)
433 integer idm_in, jdm_in,
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)
446 integer i,ii,ip,j,jj,jp
447 integer ki,kj,iii,jjj
452 data s / 1.0, 2.0, 1.0,
455 real,
parameter :: spval=2.0**100
461 if (m_out(ii,jj).eq.1)
then
466 if (i.ne.idm_in)
then
481 if (jjj>jdm_in) jjj=jdm_in
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)
496 a_out( ii,jj) = sa/ss
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)
519 print *,
"Output ocean point:", count
523 subroutine landfill(a,mask,m,n, iv,if,il,jf,jl)
526 integer m,n,mask(m,n), iv(n,2),if,il,jf,jl
534 integer,
allocatable :: mm(:,:,:)
536 integer i,ii,ip0,ip1,ipass,j,jj,ki,kj,nleft,nup
544 data lfirst / .true. /
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 /
556 allocate( mm(0:m+1,0:n+1,0:1) )
560 mm( : , : ,1) = mm(:,:,0)
568 &
'landfill - m,n,if,il,jf,jl =',m,n,
if,il,jf,jl
576 do i= iv(j,1),iv(j,2)
577 if (mm(i,j,ip0).eq.2)
then
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)
616 write(6,
'(a,i4,a,i6,a,i6,a)')
617 &
'landfill: pass',ipass,
619 &
' points, with',nleft,
' still to fill'
625 mm(if:il,jf:jl,ip0) = mm(if:il,jf:jl,ip1)
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'
655 subroutine psmooth(a,mask,amn,amx,m,n)
658 integer m,n,mask(m,n)
659 real a(m,n),amn(m,n),amx(m,n)
663 integer,
allocatable :: mm(:,:)
664 real,
allocatable :: aa(:,:)
666 integer i,ii,j,jj,ki,kj
671 data s / 1.0, 2.0, 1.0,
675 rss = 1.0/sum(s(:,:))
684 allocate( mm(0:m+1,0:n+1) )
693 if (mm(i,j).eq.1)
then
699 if (mm(ii,jj).eq.1)
then
700 sa = sa + s(ki,kj)*aa(ii,jj)
702 sa = sa + s(ki,kj)*aa(i ,j )
706 a(i,j) =
max( amn(i,j),
707 &
min( amx(i,j), sa*rss ) )
720 print *,
"NetCDF return error ", status