120subroutine handle_grib_error(vname,lev,method,value,varnum,read_from_input, iret,var,var8,var3d)
122 use,
intrinsic :: ieee_arithmetic
127 real(esmf_kind_r4),
intent(in) :: value
128 logical,
intent(inout) :: read_from_input(:)
129 real(esmf_kind_r4),
intent(inout),
optional :: var(:,:)
130 real(esmf_kind_r8),
intent(inout),
optional :: var8(:,:)
131 real(esmf_kind_r8),
intent(inout),
optional :: var3d(:,:,:)
133 character(len=20),
intent(in) :: vname, lev, method
134 character(len=200) :: err_msg
136 integer,
intent(in) :: varnum
137 integer,
intent(inout) :: iret
140 if (varnum == 9999)
then
141 print*,
"WARNING: ", trim(vname),
" NOT FOUND AT LEVEL ", lev,
" IN EXTERNAL FILE ", &
142 "AND NO ENTRY EXISTS IN VARMAP TABLE. VARIABLE WILL NOT BE USED."
148 if (trim(method) ==
"skip" )
then
149 print*,
"WARNING: SKIPPING ", trim(vname),
" IN FILE"
150 read_from_input(varnum) = .false.
152 elseif (trim(method) ==
"set_to_fill")
then
153 print*,
"WARNING: ,", trim(vname),
" NOT AVAILABLE AT LEVEL ", trim(lev), &
154 ". SETTING EQUAL TO FILL VALUE OF ",
value
155 if(
present(var)) var(:,:) =
value
156 if(
present(var8)) var8(:,:) =
value
157 if(
present(var3d)) var3d(:,:,:) =
value
158 elseif (trim(method) ==
"set_to_NaN")
then
159 print*,
"WARNING: ,", trim(vname),
" NOT AVAILABLE AT LEVEL ", trim(lev), &
160 ". SETTING EQUAL TO NaNs"
161 if(
present(var)) var(:,:) = ieee_value(var,ieee_quiet_nan)
162 if(
present(var8)) var8(:,:) = ieee_value(var8,ieee_quiet_nan)
163 if(
present(var3d)) var3d(:,:,:) = ieee_value(var3d,ieee_quiet_nan)
164 elseif (trim(method) ==
"stop")
then
165 err_msg=
"READING " // trim(vname) //
" at level " //lev//
". TO MAKE THIS NON-" // &
166 "FATAL, CHANGE STOP TO SKIP FOR THIS VARIABLE IN YOUR VARMAP FILE."
167 call error_handler(err_msg, iret)
168 elseif (trim(method) ==
"intrp")
then
169 print*,
"WARNING: ,"//trim(vname)//
" NOT AVAILABLE AT LEVEL "//trim(lev)// &
170 ". WILL INTERPOLATE INTERSPERSED MISSING LEVELS AND/OR FILL MISSING"//&
173 err_msg=
"ERROR USING MISSING_VAR_METHOD. PLEASE SET VALUES IN" // &
174 " VARMAP TABLE TO ONE OF: set_to_fill, set_to_NaN, intrp, skip, or stop."
175 call error_handler(err_msg, 1)
229subroutine check_soilt(soilt, landmask, skint,ICET_DEFAULT,i_input,j_input,lsoil_input)
232 integer,
intent(in) :: i_input, j_input, lsoil_input
233 real(esmf_kind_r8),
intent(inout) :: soilt(i_input,j_input,lsoil_input)
234 real(esmf_kind_r8),
intent(in) :: skint(i_input,j_input)
235 real,
intent(in) :: ICET_DEFAULT
236 integer(esmf_kind_i4),
intent(in) :: landmask(i_input,j_input)
243 if (landmask(i,j) == 0_esmf_kind_i4 )
then
244 soilt(i,j,k) = skint(i,j)
245 else if (landmask(i,j) == 1_esmf_kind_i4 .and. soilt(i,j,k) > 350.0_esmf_kind_r8)
then
246 soilt(i,j,k) = skint(i,j)
247 else if (landmask(i,j) == 2_esmf_kind_i4 )
then
248 soilt(i,j,k) = icet_default
264subroutine check_cnwat(cnwat,i_input,j_input)
267 integer,
intent(in) :: i_input, j_input
268 real(esmf_kind_r8),
intent(inout) :: cnwat(i_input,j_input)
270 real(esmf_kind_r8) :: max_cnwat = 0.5
276 if (cnwat(i,j) .gt. max_cnwat) cnwat(i,j) = 0.0_esmf_kind_r8
299SUBROUTINE dint2p(PPIN,XXIN,NPIN,PPOUT,XXOUT,NPOUT &
315 INTEGER NPIN,NPOUT,LINLOG,IER
316 real*8 ppin(npin),xxin(npin),ppout(npout),xmsg
320 real*8 pin(npin),xin(npin),p(npin),x(npin)
321 real*8 pout(npout),xout(npout)
324 INTEGER NP,NL,NLMAX,NLSAVE,NP1,NO1,N1,N2,LOGLIN, &
326 real*8 slope,pa,pb,pc
342 IF (npin.LT.2 .OR. npout.LT.1) ier = ier + 1
355 IF (ppin(1).LT.ppin(2))
THEN
358 IF (ppout(1).LT.ppout(2))
THEN
363 pin(np) = ppin(abs(np1-np))
364 xin(np) = xxin(abs(np1-np))
368 pout(np) = ppout(abs(no1-np))
376 IF (xin(np).NE.xmsg .AND. pin(np).NE.xmsg)
THEN
387 print *,
'INT2P: ier=',ier
407 IF (pout(np).EQ.p(nl))
THEN
416 IF (loglin.EQ.1)
THEN
419 IF (pout(np).LT.p(nl) .AND. pout(np).GT.p(nl+1))
THEN
420 slope = (x(nl)-x(nl+1))/ (p(nl)-p(nl+1))
421 xout(np) = x(nl+1) + slope* (pout(np)-p(nl+1))
428 IF (pout(np).LT.p(nl) .AND. pout(np).GT.p(nl+1))
THEN
432 if (p(nl+1).gt.0.d0)
then
438 slope = (x(nl)-x(nl+1))/ (pa-pc)
439 xout(np) = x(nl+1) + slope* (pb-pc)
448 IF (linlog.LT.0)
THEN
451 IF (pout(np).GT.p(1))
THEN
452 IF (loglin.EQ.1)
THEN
453 slope = (x(2)-x(1))/ (p(2)-p(1))
454 xout(np) = x(1) + slope* (pout(np)-p(1))
459 slope = (x(2)-x(1))/ (pa-pc)
460 xout(np) = x(1) + slope* (pb-pc)
462 ELSE IF (pout(np).LT.p(nlmax))
THEN
465 IF (loglin.EQ.1)
THEN
466 slope = (x(n1)-x(n2))/ (p(n1)-p(n2))
467 xout(np) = x(n1) + slope* (pout(np)-p(n1))
472 slope = (x(n1)-x(n2))/ (pa-pc)
474 xout(np) = x(n1) + slope* (pb-pa)