C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_sla_read.F,v 1.1 2009/11/03 03:32:25 gforget Exp $
C $Name: $
#include "COST_CPPOPTIONS.h"
subroutine COST_SLA_READ( sla_file, sla_startdate, sla_period,
I sla_intercept, sla_slope,
O sla_obs, sla_mask,
I irec, mythid )
c ==================================================================
c SUBROUTINE cost_sla_read
c ==================================================================
c
c o Read a given record of the SLA data.
c
c started: Gael Forget 20-Oct-2009
c
c ==================================================================
c SUBROUTINE cost_sla_read
c ==================================================================
implicit none
c == global variables ==
#include "EEPARAMS.h"
#include "SIZE.h"
#include "PARAMS.h"
#include "GRID.h"
#include "cal.h"
#include "ecco_cost.h"
c == routine arguments ==
integer irec
integer mythid
c == local variables ==
integer bi,bj
integer i,j,k
integer itlo,ithi
integer jtlo,jthi
integer jmin,jmax
integer imin,imax
integer sshrec
integer difftime(4)
integer middate(4)
integer noffset
_RL diffsecs
_RL spval
_RL factor
integer sla_startdate(4)
_RL sla_period
_RL sla_intercept
_RL sla_slope
_RL sla_obs (1-olx:snx+olx,1-oly:sny+oly, nsx,nsy)
_RL sla_mask (1-olx:snx+olx,1-oly:sny+oly, nsx,nsy)
character*(MAX_LEN_FNAM) sla_file
cnew(
integer il
_RL daytime
integer dayiter
integer daydate(4)
integer yday, ymod
integer md, dd, sd, ld, wd
character*(80) fnametmp
logical exst
cnew)
c == external functions ==
integer ilnblnk
external
c == end of interface ==
jtlo = mybylo(mythid)
jthi = mybyhi(mythid)
itlo = mybxlo(mythid)
ithi = mybxhi(mythid)
jmin = 1
jmax = sny
imin = 1
imax = snx
factor = 0.01
spval = -9990.
cnew(
daytime = FLOAT(secondsperday*(irec-1)) + modelstart
dayiter = hoursperday*(irec-1)+modeliter0
call CAL_GETDATE( dayiter, daytime, daydate, mythid )
call CAL_CONVDATE( daydate,yday,md,dd,sd,ld,wd,mythid )
ymod = sla_startdate(1)/10000
if ( ymod .EQ. yday ) then
middate(1) = modelstartdate(1)
else
middate(1) = yday*10000+100+1
endif
middate(2) = 0
middate(3) = modelstartdate(3)
middate(4) = modelstartdate(4)
call CAL_TIMEPASSED( middate, daydate, difftime, mythid )
call CAL_TOSECONDS( difftime, diffsecs, mythid )
sshrec = int(diffsecs/sla_period) + 1
il=ilnblnk(sla_file)
write(fnametmp(1:80),'(2a,i4)')
& sla_file(1:il), '_', yday
inquire( file=fnametmp, exist=exst )
if (.NOT. exst) then
write(fnametmp(1:80),'(a)') sla_file(1:il)
sshrec = irec
endif
cnew)
call MDSREADFIELD( fnametmp, cost_iprec, cost_yftype, 1, sla_obs,
& sshrec, mythid )
do bj = jtlo,jthi
do bi = itlo,ithi
k = 1
do j = jmin,jmax
do i = imin,imax
if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
sla_mask(i,j,bi,bj) = 0. _d 0
else
sla_mask(i,j,bi,bj) = 1. _d 0
endif
if (sla_obs(i,j,bi,bj) .le. spval) then
sla_mask(i,j,bi,bj) = 0. _d 0
endif
if (abs(sla_obs(i,j,bi,bj)) .lt. 1.d-8 ) then
sla_mask(i,j,bi,bj) = 0. _d 0
endif
cph(
if ( R_low(i,j,bi,bj) .GT. -200. ) then
sla_mask(i,j,bi,bj) = 0. _d 0
endif
cph)
sla_mask(i,j,bi,bj) = sla_mask(i,j,bi,bj)*frame(i,j)
sla_obs(i,j,bi,bj) = sla_mask(i,j,bi,bj)*factor*
& ( sla_obs(i,j,bi,bj) -
& ( sla_intercept + sla_slope*irec*hoursperday ) )
enddo
enddo
enddo
enddo
return
end