7 use esmf,
only: esmf_clock, esmf_time, esmf_timeinterval
8 use esmf,
only: esmf_clockget, esmf_timeget, esmf_timeintervalget
9 use seq_cdata_mod,
only: seq_cdata, seq_cdata_setptrs
10 use seq_flds_mod,
only: seq_flds_x2o_fields, seq_flds_o2x_fields
11 use mct_mod,
only: mct_gsmap, mct_gsmap_init, mct_gsmap_lsize, &
12 mct_gsmap_orderedpoints
13 use mct_mod,
only: mct_avect, mct_avect_init, mct_avect_zero, &
15 use mct_mod,
only: mct_ggrid, mct_ggrid_init, mct_ggrid_importrattr, &
17 use seq_infodata_mod,
only: seq_infodata_type, seq_infodata_getdata, &
18 seq_infodata_start_type_start, seq_infodata_start_type_cont, &
19 seq_infodata_start_type_brnch, seq_infodata_putdata
20 use seq_comm_mct,
only: seq_comm_name, seq_comm_inst, seq_comm_suffix
21 use seq_timemgr_mod,
only: seq_timemgr_eclockgetdata, seq_timemgr_restartalarmison
22 use perf_mod,
only: t_startf, t_stopf
23 use shr_file_mod,
only: shr_file_getunit, shr_file_freeunit, shr_file_setio, &
24 shr_file_getlogunit, shr_file_getloglevel, &
25 shr_file_setlogunit, shr_file_setloglevel
36 use mom_time_manager,
only: time_type, set_date, set_time, set_calendar_type, noleap
37 use mom_time_manager,
only:
operator(+),
operator(-),
operator(*),
operator(/)
38 use mom_time_manager,
only:
operator(==),
operator(/=),
operator(>), get_time
41 use mom_eos,
only: gsw_sp_from_sr, gsw_pt_from_ct
44 use mpp_domains_mod,
only: mpp_get_compute_domain
54 use time_interp_external_mod,
only : time_interp_external
60 use coupler_types_mod,
only : coupler_type_spawn
61 use coupler_types_mod,
only : coupler_type_initialized, coupler_type_copy_data
64 implicit none;
private
66 #include <MOM_memory.h>
80 logical,
parameter ::
debug=.true.
87 type(seq_infodata_type),
pointer :: infodata
90 real :: c1, c2, c3, c4
92 character(len=384) :: pointer_filename
104 subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
105 type(esmf_clock),
intent(inout) :: eclock
107 type(seq_cdata) ,
intent(inout) :: cdata_o
108 type(mct_avect) ,
intent(inout) :: x2o_o
109 type(mct_avect) ,
intent(inout) :: o2x_o
110 character(len=*),
optional ,
intent(in) :: nlfilename
113 type(time_type) :: time0
114 type(time_type) :: time_start
115 type(esmf_time) :: time_var
116 type(esmf_time) :: time_in_esmf
117 type(esmf_timeinterval) :: ocn_cpl_interval
118 integer :: ncouple_per_day
119 integer :: year, month, day, hour, minute, seconds, seconds_n, seconds_d, rc
120 character(len=240) :: runid
121 character(len=32) :: runtype
122 character(len=240) :: restartfile
124 character(len=240) :: restart_pointer_file
125 character(len=240) :: restartpath
126 integer :: mpicom_ocn
128 integer :: i, errorcode
129 integer :: lsize, nsend, nrecv
130 logical :: ldiag_cpl = .false.
131 integer :: isc, iec, jsc, jec, ni, nj
136 character(len=40) :: mdl =
"ocn_comp_mct"
139 integer :: mom_mct_id
140 type(mct_gsmap),
pointer :: mom_mct_gsmap => null()
141 type(mct_ggrid),
pointer :: mom_mct_dom => null()
142 type(mct_gsmap) :: mom_mct_gsmap3d
143 type(mct_ggrid) :: mom_mct_dom3d
146 integer :: ocn_cpl_dt
147 real (kind=8) :: mom_cpl_dt
148 real (kind=8), parameter :: &
149 seconds_in_minute = 60.0d0, &
150 seconds_in_hour = 3600.0d0, &
151 seconds_in_day = 86400.0d0, &
152 minutes_in_hour = 60.0d0
154 character(len=99) :: ocn_modelio_name
155 integer :: shrlogunit
158 integer(kind=4) :: inst_index
159 character(len=16) :: inst_name
160 character(len=16) :: inst_suffix
166 character(len=128) :: err_msg
169 call seq_cdata_setptrs(cdata_o, id=mom_mct_id, mpicom=mpicom_ocn, &
170 gsmap=mom_mct_gsmap, dom=mom_mct_dom, infodata=
glb%infodata)
175 call seq_infodata_getdata(
glb%infodata, case_name=runid )
178 inst_name = seq_comm_name(mom_mct_id)
179 inst_index = seq_comm_inst(mom_mct_id)
180 inst_suffix = seq_comm_suffix(mom_mct_id)
182 call t_startf(
'MOM_init')
185 call mom_infra_init(mpicom_ocn)
191 call shr_file_getlogunit (shrlogunit)
192 call shr_file_getloglevel(shrloglev)
194 glb%stdout = shr_file_getunit()
197 ocn_modelio_name =
'ocn_modelio.nml' // trim(inst_suffix)
198 call shr_file_setio(ocn_modelio_name,
glb%stdout)
201 call shr_file_setlogunit(
glb%stdout)
204 call set_calendar_type(noleap)
207 call esmf_clockget(eclock, starttime=time_var, rc=rc)
208 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
209 time0 = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
212 call esmf_clockget(eclock, currtime=time_var, rc=rc)
213 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
214 time_start = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
218 write(
glb%stdout,*)
'ocn_init_mct, current time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
220 call esmf_clockget(eclock, starttime=time_var, rc=rc)
221 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
222 write(
glb%stdout,*)
'ocn_init_mct, start time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
224 call esmf_clockget(eclock, stoptime=time_var, rc=rc)
225 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
226 write(
glb%stdout,*)
'ocn_init_mct, stop time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
228 call esmf_clockget(eclock, prevtime=time_var, rc=rc)
229 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
230 write(
glb%stdout,*)
'ocn_init_mct, previous time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
232 call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
233 call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
234 write(
glb%stdout,*)
'ocn_init_mct, time step: y,m,d-',year,month,day,
's,sn,sd=',seconds,seconds_n,seconds_d
240 allocate(
glb%ocn_public)
241 glb%ocn_public%is_ocean_PE = .true.
243 allocate(
glb%ocn_public%pelist(npes))
244 glb%ocn_public%pelist(:) = (/(i,i=pe0,pe0+npes)/)
249 call get_mom_input(param_file, dirs_tmp, check_params=.false.)
252 call get_param(param_file, mdl,
"POINTER_FILENAME",
glb%pointer_filename, &
253 "Name of the ascii file that contains the path and filename of" // &
254 " the latest restart file.", default=
'rpointer.ocn')
256 call get_param(param_file, mdl,
"SW_DECOMP",
glb%sw_decomp, &
257 "If True, read coeffs c1, c2, c3 and c4 and decompose" // &
258 "the net shortwave radiation (SW) into four components:\n" // &
259 "visible, direct shortwave = c1 * SW \n" // &
260 "visible, diffuse shortwave = c2 * SW \n" // &
261 "near-IR, direct shortwave = c3 * SW \n" // &
262 "near-IR, diffuse shortwave = c4 * SW", default=.true.)
264 if (
glb%sw_decomp)
then
266 "Coeff. used to convert net shortwave rad. into "//&
267 "visible, direct shortwave.", units=
"nondim", default=0.285)
270 "Coeff. used to convert net shortwave rad. into "//&
271 "visible, diffuse shortwave.", units=
"nondim", default=0.285)
274 "Coeff. used to convert net shortwave rad. into "//&
275 "near-IR, direct shortwave.", units=
"nondim", default=0.215)
278 "Coeff. used to convert net shortwave rad. into "//&
279 "near-IR, diffuse shortwave.", units=
"nondim", default=0.215)
289 if (runtype ==
"initial")
then
291 call ocean_model_init(
glb%ocn_public,
glb%ocn_state, time0, time_start, input_restart_file =
'n')
294 call seq_infodata_getdata(
glb%infodata, outpathroot=restartpath )
296 nu = shr_file_getunit()
297 restart_pointer_file = trim(
glb%pointer_filename)
298 if (
is_root_pe())
write(
glb%stdout,*)
'Reading ocn pointer file: ',restart_pointer_file
299 open(nu, file=restart_pointer_file, form=
'formatted', status=
'unknown')
300 read(nu,
'(a)') restartfile
304 write(
glb%stdout,*)
'Reading restart file: ',trim(restartfile)
306 call shr_file_freeunit(nu)
307 call ocean_model_init(
glb%ocn_public,
glb%ocn_state, time0, time_start, input_restart_file=trim(restartfile))
310 write(
glb%stdout,
'(/12x,a/)')
'======== COMPLETED MOM INITIALIZATION ========'
317 glb%grid =>
glb%ocn_state%grid
323 call t_stopf(
'MOM_init')
326 call t_startf(
'MOM_mct_init')
328 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling ocn_SetGSMap_mct"
332 call ocn_setgsmap_mct(mpicom_ocn, mom_mct_id, mom_mct_gsmap, mom_mct_gsmap3d)
333 lsize = mct_gsmap_lsize(mom_mct_gsmap, mpicom_ocn)
337 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling ocn_domain_mct"
343 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling mct_avect_init a"
346 call mct_avect_init(x2o_o, rlist=seq_flds_x2o_fields, lsize=lsize)
348 call mct_avect_zero(x2o_o)
350 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling mct_avect_init b"
353 call mct_avect_init(o2x_o, rlist=seq_flds_o2x_fields, lsize=lsize)
355 call mct_avect_zero(o2x_o)
358 nsend = mct_avect_nrattr(o2x_o)
359 nrecv = mct_avect_nrattr(x2o_o)
363 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling seq_timemgr_eclockgetdata"
365 call seq_timemgr_eclockgetdata(eclock, dtime=ocn_cpl_dt)
368 ncouple_per_day = seconds_in_day / ocn_cpl_dt
369 mom_cpl_dt = seconds_in_day / ncouple_per_day
370 if (mom_cpl_dt /= ocn_cpl_dt)
then
371 write(
glb%stdout,*)
'ERROR mom_cpl_dt and ocn_cpl_dt must be identical'
382 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling ocn_export"
383 call ocn_export(
glb%ind,
glb%ocn_public,
glb%grid, o2x_o%rattr, mom_cpl_dt, ncouple_per_day)
385 call t_stopf(
'MOM_mct_init')
390 if (
debug .and. root_pe().eq.pe_here()) print *,
"calling seq_infodata_putdata"
392 call seq_infodata_putdata(
glb%infodata, &
393 ocn_nx = ni , ocn_ny = nj)
394 call seq_infodata_putdata(
glb%infodata, &
395 ocn_prognostic=.true., ocnrof_prognostic=.true.)
397 if (
debug .and. root_pe().eq.pe_here()) print *,
"leaving ocean_init_mct"
401 call shr_file_setlogunit (shrlogunit)
402 call shr_file_setloglevel(shrloglev)
410 subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
411 type(esmf_clock),
intent(inout) :: eclock
412 type(seq_cdata),
intent(inout) :: cdata_o
413 type(mct_avect),
intent(inout) :: x2o_o
414 type(mct_avect),
intent(inout) :: o2x_o
416 type(esmf_time) :: time_var
417 type(esmf_timeinterval) :: ocn_cpl_interval
418 integer :: year, month, day, hour, minute, seconds, seconds_n, seconds_d, rc
419 logical :: write_restart_at_eod
420 logical ::
debug=.false.
421 type(time_type) :: time_start
422 type(time_type) :: coupling_timestep
423 character(len=128) :: err_msg
424 character(len=32) :: timestamp
425 character(len=384) :: restartname
426 character(len=384) :: restart_pointer_file
427 character(len=384) :: runid
428 character(len=32) :: runtype
430 integer :: shrlogunit
432 logical,
save :: firstcall = .true.
433 real (kind=8), parameter :: seconds_in_day = 86400.0
434 integer :: ocn_cpl_dt
435 real (kind=8) :: mom_cpl_dt
436 integer :: ncouple_per_day
440 call shr_file_getlogunit(shrlogunit)
441 call shr_file_getloglevel(shrloglev)
442 call shr_file_setlogunit(
glb%stdout)
446 call esmf_clockget(eclock, prevtime=time_var, rc=rc)
447 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
448 time_start = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
451 call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
452 call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
453 coupling_timestep = set_time(seconds, days=day, err_msg=err_msg)
455 call seq_timemgr_eclockgetdata(eclock, dtime=ocn_cpl_dt)
456 ncouple_per_day = seconds_in_day / ocn_cpl_dt
457 mom_cpl_dt = seconds_in_day / ncouple_per_day
466 if (runtype /=
"continue" .and. runtype /=
"branch")
then
469 write(
glb%stdout,*)
'doubling first interval duration!'
473 time_start = time_start-coupling_timestep
475 coupling_timestep = coupling_timestep*2
483 call esmf_clockget(eclock, currtime=time_var, rc=rc)
484 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
485 write(
glb%stdout,*)
'ocn_run_mct, current time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
486 call esmf_clockget(eclock, starttime=time_var, rc=rc)
487 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
488 write(
glb%stdout,*)
'ocn_run_mct, start time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
489 call esmf_clockget(eclock, stoptime=time_var, rc=rc)
490 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
491 write(
glb%stdout,*)
'ocn_run_mct, stop time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
492 call esmf_clockget(eclock, prevtime=time_var, rc=rc)
493 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
494 write(
glb%stdout,*)
'ocn_run_mct, previous time: y,m,d-',year,month,day,
'h,m,s=',hour,minute,seconds
495 call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
496 call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
497 write(
glb%stdout,*)
'ocn_init_mct, time step: y,m,d-',year,month,day,
's,sn,sd=',seconds,seconds_n,seconds_d
503 call seq_cdata_setptrs(cdata_o, infodata=
glb%infodata)
509 if (
glb%sw_decomp)
then
520 call ocn_export(
glb%ind,
glb%ocn_public,
glb%grid, o2x_o%rattr, mom_cpl_dt, ncouple_per_day)
524 write_restart_at_eod = seq_timemgr_restartalarmison(eclock)
525 if (
debug .and.
is_root_pe())
write(
glb%stdout,*)
'ocn_run_mct, write_restart_at_eod=', write_restart_at_eod
527 if (write_restart_at_eod)
then
529 call seq_infodata_getdata(
glb%infodata, case_name=runid )
531 call esmf_clockget(eclock, currtime=time_var, rc=rc)
532 call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
533 seconds = seconds + hour*3600 + minute*60
534 write(restartname,
'(A,".mom6.r.",I4.4,"-",I2.2,"-",I2.2,"-",I5.5)') trim(runid), year, month, day, seconds
537 glb%ocn_state%restart_CSp, .false., filename=restartname, gv=
glb%ocn_state%GV)
540 nu = shr_file_getunit()
542 restart_pointer_file = trim(
glb%pointer_filename)
543 open(nu, file=restart_pointer_file, form=
'formatted', status=
'unknown')
544 write(nu,
'(a)') trim(restartname) //
'.nc'
546 write(
glb%stdout,*)
'ocn restart pointer file written: ',trim(restartname)
548 call shr_file_freeunit(nu)
552 glb%ocn_state%dirs%restart_output_dir, .true.)
555 if (
glb%ocn_state%use_ice_shelf)
then
557 glb%ocn_state%dirs%restart_output_dir, .true.)
564 call shr_file_setlogunit(shrlogunit)
565 call shr_file_setloglevel(shrloglev)
576 type(esmf_clock) ,
intent(inout) :: eclock
577 type(seq_cdata) ,
intent(inout) :: cdata_o
578 type(mct_avect) ,
intent(inout) :: x2o_o
579 type(mct_avect) ,
intent(inout) :: o2x_o
581 call ocean_model_end(
glb%ocn_public,
glb%ocn_state,
glb%ocn_state%Time)
591 integer,
intent(in) :: mpicom_ocn
592 integer,
intent(in) :: mom_mct_id
593 type(mct_gsmap),
intent(inout) :: gsmap_ocn
594 type(mct_gsmap),
intent(inout) :: gsmap3d_ocn
602 integer,
allocatable :: gindex(:)
605 if (.not.
associated(grid))
call mom_error(fatal,
'ocn_comp_mct.F90, ocn_SetGSMap_mct():' // &
606 'grid is not associated!')
609 lsize = ( grid%iec - grid%isc + 1 ) * ( grid%jec - grid%jsc + 1 )
615 allocate(gindex(lsize))
619 do j = grid%jsc, grid%jec
620 jg = j + grid%jdg_offset
621 do i = grid%isc, grid%iec
622 ig = i + grid%idg_offset
624 gindex(k) = ni * (jg - 1) + ig
629 call mct_gsmap_init(gsmap_ocn, gindex, mpicom_ocn, mom_mct_id, lsize, ni * nj)
639 integer ,
intent(in) :: lsize
640 type(mct_gsmap),
intent(in) :: gsmap_ocn
641 type(mct_ggrid),
intent(inout) :: dom_ocn
644 integer,
parameter :: shr_real_r8 = selected_real_kind(12)
645 integer,
pointer :: idata(:)
647 real(kind=shr_real_r8),
pointer ::
data(:)
648 real(kind=shr_real_r8) :: l2_to_rad2
654 call mct_ggrid_init(ggrid=dom_ocn, coordchars=
'lat:lon:hgt', otherchars=
'area:aream:mask:frac', lsize=lsize )
656 call mct_avect_zero(dom_ocn%data)
657 allocate(
data(lsize))
661 call mct_gsmap_orderedpoints(gsmap_ocn, k, idata)
662 call mct_ggrid_importiattr(dom_ocn,
'GlobGridNum',idata,lsize)
666 call mct_ggrid_importrattr(dom_ocn,
"lat" ,
data,lsize)
667 call mct_ggrid_importrattr(dom_ocn,
"lon" ,
data,lsize)
668 call mct_ggrid_importrattr(dom_ocn,
"area" ,
data,lsize)
669 call mct_ggrid_importrattr(dom_ocn,
"aream",
data,lsize)
671 call mct_ggrid_importrattr(dom_ocn,
"mask",
data,lsize)
672 call mct_ggrid_importrattr(dom_ocn,
"frac",
data,lsize)
675 do j = grid%jsc, grid%jec
676 do i = grid%isc, grid%iec
678 data(k) = grid%geoLonT(i,j)
681 call mct_ggrid_importrattr(dom_ocn,
"lon",
data,lsize)
684 do j = grid%jsc, grid%jec
685 do i = grid%isc, grid%iec
687 data(k) = grid%geoLatT(i,j)
690 call mct_ggrid_importrattr(dom_ocn,
"lat",
data,lsize)
693 l2_to_rad2 = grid%US%L_to_m**2 / grid%Rad_Earth**2
694 do j = grid%jsc, grid%jec
695 do i = grid%isc, grid%iec
697 data(k) = grid%AreaT(i,j) * l2_to_rad2
700 call mct_ggrid_importrattr(dom_ocn,
"area",
data,lsize)
703 do j = grid%jsc, grid%jec
704 do i = grid%isc, grid%iec
706 data(k) = grid%mask2dT(i,j)
709 call mct_ggrid_importrattr(dom_ocn,
"mask",
data,lsize)
710 call mct_ggrid_importrattr(dom_ocn,
"frac",
data,lsize)
721 character(len=32) :: starttype
723 call seq_infodata_getdata(
glb%infodata, start_type=starttype)
725 if ( trim(starttype) == trim(seq_infodata_start_type_start))
then
727 else if (trim(starttype) == trim(seq_infodata_start_type_cont) )
then
729 else if (trim(starttype) == trim(seq_infodata_start_type_brnch))
then
732 write(
glb%stdout,*)
'ocn_comp_mct ERROR: unknown starttype'
747 integer :: is, ie, js, je
749 is = os%grid%isc ; ie = os%grid%iec ; js = os%grid%jsc ; je = os%grid%jec
750 call coupler_type_spawn(ocean_sfc%fields, os%sfc_state%tr_fields, &
751 (/is,is,ie,ie/), (/js,js,je,je/), as_needed=.true.)
826 integer,
intent(in) :: isc, iec, jsc, jec
828 allocate ( iob% rofl_flux (isc:iec,jsc:jec), &
829 iob% rofi_flux (isc:iec,jsc:jec), &
830 iob% u_flux (isc:iec,jsc:jec), &
831 iob% v_flux (isc:iec,jsc:jec), &
832 iob% t_flux (isc:iec,jsc:jec), &
833 iob% seaice_melt_heat (isc:iec,jsc:jec),&
834 iob% seaice_melt (isc:iec,jsc:jec), &
835 iob% q_flux (isc:iec,jsc:jec), &
836 iob% salt_flux (isc:iec,jsc:jec), &
837 iob% lw_flux (isc:iec,jsc:jec), &
838 iob% sw_flux_vis_dir (isc:iec,jsc:jec), &
839 iob% sw_flux_vis_dif (isc:iec,jsc:jec), &
840 iob% sw_flux_nir_dir (isc:iec,jsc:jec), &
841 iob% sw_flux_nir_dif (isc:iec,jsc:jec), &
842 iob% lprec (isc:iec,jsc:jec), &
843 iob% fprec (isc:iec,jsc:jec), &
844 iob% ustar_berg (isc:iec,jsc:jec), &
845 iob% area_berg (isc:iec,jsc:jec), &
846 iob% mass_berg (isc:iec,jsc:jec), &
847 iob% calving (isc:iec,jsc:jec), &
848 iob% runoff_hflx (isc:iec,jsc:jec), &
849 iob% calving_hflx (isc:iec,jsc:jec), &
850 iob% mi (isc:iec,jsc:jec), &
851 iob% p (isc:iec,jsc:jec))
858 iob%seaice_melt_heat = 0.0
859 iob%seaice_melt = 0.0
863 iob%sw_flux_vis_dir = 0.0
864 iob%sw_flux_vis_dif = 0.0
865 iob%sw_flux_nir_dir = 0.0
866 iob%sw_flux_nir_dif = 0.0
873 iob%runoff_hflx = 0.0
874 iob%calving_hflx = 0.0