Skip to content

Commit

Permalink
updates for RASM (#593)
Browse files Browse the repository at this point in the history
  • Loading branch information
apcraig authored Apr 9, 2021
1 parent 9b51179 commit 2378740
Show file tree
Hide file tree
Showing 8 changed files with 46 additions and 46 deletions.
4 changes: 2 additions & 2 deletions cicecore/cicedynB/infrastructure/ice_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2401,7 +2401,7 @@ subroutine get_bathymetry
do iblk = 1, nblocks
do j = 1, ny_block
do i = 1, nx_block
k = nint(kmt(i,j,iblk))
k = min(nint(kmt(i,j,iblk)),nlevel)
if (k > nlevel) call abort_ice(subname//' kmt gt nlevel error')
if (k > 0) bathymetry(i,j,iblk) = depth(k)
enddo
Expand Down Expand Up @@ -2433,7 +2433,7 @@ subroutine get_bathymetry_popfile

character(len=*), parameter :: subname = '(get_bathymetry_popfile)'

ntmp = maxval(KMT)
ntmp = maxval(nint(KMT))
nlevel = global_maxval(ntmp,distrb_info)

if (my_task==master_task) then
Expand Down
4 changes: 2 additions & 2 deletions cicecore/drivers/mct/cesm1/CICE_RunMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ subroutine ice_step

use ice_boundary, only: ice_HaloUpdate
use ice_calendar, only: dt, dt_dyn, ndtd, diagfreq, write_restart, istep
use ice_calendar, only: idate, sec
use ice_calendar, only: idate, msec
use ice_diagnostics, only: init_mass_diags, runtime_diags
use ice_diagnostics_bgc, only: hbrine_diags, zsal_diags, bgc_diags
use ice_domain, only: halo_info, nblocks
Expand Down Expand Up @@ -209,7 +209,7 @@ subroutine ice_step
if (prescribed_ice) then ! read prescribed ice
call t_barrierf('cice_run_presc_BARRIER',MPI_COMM_ICE)
call t_startf ('cice_run_presc')
call ice_prescribed_run(idate, sec)
call ice_prescribed_run(idate, msec)
call t_stopf ('cice_run_presc')
endif

Expand Down
26 changes: 13 additions & 13 deletions cicecore/drivers/mct/cesm1/ice_comp_esmf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,10 @@ module ice_comp_esmf
use ice_constants, only : c0, c1, spval_dbl, rad_to_deg, radius, secday
use ice_communicate, only : my_task, master_task, MPI_COMM_ICE
use ice_calendar, only : istep, istep1, force_restart_now, write_ic,&
idate, idate0, mday, time, month, &
sec, dt, dt_dyn, calendar, &
idate, idate0, mday, time, mmonth, &
msec, dt, dt_dyn, calendar, &
calendar_type, nextsw_cday, days_per_year, &
nyr, new_year, time2sec, year_init
myear, new_year, time2sec, year_init
use icepack_orbital, only : eccen, obliqr, lambm0, mvelpp
use ice_timers

Expand Down Expand Up @@ -178,7 +178,7 @@ subroutine ice_init_esmf(comp, import_state, export_state, EClock, rc)
integer :: ref_ymd ! Reference date (YYYYMMDD)
integer :: ref_tod ! reference time of day (s)
integer :: iyear ! yyyy
integer :: nyrp ! yyyy
integer :: myearp ! yyyy
integer :: dtime ! time step
integer :: shrlogunit,shrloglev ! old values
integer :: iam,ierr
Expand Down Expand Up @@ -366,17 +366,17 @@ subroutine ice_init_esmf(comp, import_state, export_state, EClock, rc)
endif

iyear = (idate/10000) ! integer year of basedate
month = (idate-iyear*10000)/100 ! integer month of basedate
mday = idate-iyear*10000-month*100 ! day of month of basedate
mmonth= (idate-iyear*10000)/100 ! integer month of basedate
mday = idate-iyear*10000-mmonth*100 ! day of month of basedate

if (my_task == master_task) then
write(nu_diag,*) trim(subname),' curr_ymd = ',curr_ymd
write(nu_diag,*) trim(subname),' cice year_init = ',year_init
write(nu_diag,*) trim(subname),' cice start date = ',idate
write(nu_diag,*) trim(subname),' cice start ymds = ',iyear,month,mday,start_tod
write(nu_diag,*) trim(subname),' cice start ymds = ',iyear,mmonth,mday,start_tod
endif

call time2sec(iyear,month,mday,time)
call time2sec(iyear,mmonth,mday,time)
time = time+start_tod

call shr_sys_flush(nu_diag)
Expand Down Expand Up @@ -640,7 +640,7 @@ subroutine ice_run_esmf(comp, import_state, export_state, EClock, rc)
integer :: curr_tod ! Current time of day (s)
integer :: shrlogunit,shrloglev ! old values
integer :: lbnum
integer :: n, nyrp
integer :: n, myearp
type(ESMF_Array) :: i2x, x2i
real(R8), pointer :: fptr(:,:)
character(len=*), parameter :: subname = '(ice_run_esmf)'
Expand Down Expand Up @@ -694,9 +694,9 @@ subroutine ice_run_esmf(comp, import_state, export_state, EClock, rc)
force_restart_now = seq_timemgr_RestartAlarmIsOn(EClock)

if (calendar_type .eq. "GREGORIAN") then
nyrp = nyr
nyr = (curr_ymd/10000)+1 ! integer year of basedate
if (nyr /= nyrp) then
myearp = myear
myear = (curr_ymd/10000)+1 ! integer year of basedate
if (myear /= myearp) then
new_year = .true.
else
new_year = .false.
Expand Down Expand Up @@ -757,7 +757,7 @@ subroutine ice_run_esmf(comp, import_state, export_state, EClock, rc)
! check that internal clock is in sync with master clock
!--------------------------------------------------------------------

tod = sec
tod = msec
ymd = idate
if (.not. seq_timemgr_EClockDateInSync( EClock, ymd, tod )) then
call seq_timemgr_EClockGetData( EClock, curr_ymd=ymd_sync, &
Expand Down
28 changes: 14 additions & 14 deletions cicecore/drivers/mct/cesm1/ice_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,8 @@ module ice_comp_mct
use ice_constants, only : ice_init_constants
use ice_communicate, only : my_task, master_task, MPI_COMM_ICE
use ice_calendar, only : istep, istep1, force_restart_now, write_ic,&
idate, idate0, mday, month, nyr, &
sec, dt, dt_dyn, calendar, &
idate, idate0, mday, mmonth, myear, &
msec, dt, dt_dyn, calendar, &
calendar_type, nextsw_cday, days_per_year
use ice_timers

Expand Down Expand Up @@ -150,7 +150,7 @@ subroutine ice_init_mct( EClock, cdata_i, x2i_i, i2x_i, NLFilename )
integer :: curr_tod ! Current time of day (s)
integer :: ref_ymd ! Reference date (YYYYMMDD)
integer :: ref_tod ! reference time of day (s)
integer :: nyrp ! yyyy
integer :: myearp ! yyyy
integer :: dtime ! time step
integer :: shrlogunit,shrloglev ! old values
integer :: iam,ierr
Expand Down Expand Up @@ -301,7 +301,7 @@ subroutine ice_init_mct( EClock, cdata_i, x2i_i, i2x_i, NLFilename )
! - istep1 is set to istep0
! - date information is determined from restart
! - on initial run
! - nyr, month, mday, sec obtained from sync clock
! - myear, mmonth, mday, msec obtained from sync clock
! - istep0 and istep1 are set to 0

call seq_timemgr_EClockGetData(EClock, &
Expand Down Expand Up @@ -336,15 +336,15 @@ subroutine ice_init_mct( EClock, cdata_i, x2i_i, i2x_i, NLFilename )
write(nu_diag,*) trim(subname),' ERROR idate lt zero',idate
call shr_sys_abort(subname//' :: ERROR idate lt zero')
endif
nyr = (idate/10000) ! integer year of basedate
month = (idate-nyr*10000)/100 ! integer month of basedate
mday = idate-nyr*10000-month*100 ! day of month of basedate
sec = start_tod ! seconds
myear = (idate/10000) ! integer year of basedate
mmonth= (idate-myear*10000)/100 ! integer month of basedate
mday = idate-myear*10000-mmonth*100 ! day of month of basedate
msec = start_tod ! seconds

if (my_task == master_task) then
write(nu_diag,*) trim(subname),' curr_ymd = ',curr_ymd
write(nu_diag,*) trim(subname),' cice start date = ',idate
write(nu_diag,*) trim(subname),' cice start ymds = ',nyr,month,mday,start_tod
write(nu_diag,*) trim(subname),' cice start ymds = ',myear,mmonth,mday,start_tod
endif

call shr_sys_flush(nu_diag)
Expand Down Expand Up @@ -512,7 +512,7 @@ subroutine ice_run_mct( EClock, cdata_i, x2i_i, i2x_i )
integer :: curr_tod ! Current time of day (s)
integer :: shrlogunit,shrloglev ! old values
integer :: lbnum
integer :: n, nyrp
integer :: n, myearp
type(mct_gGrid) , pointer :: dom_i
type(seq_infodata_type), pointer :: infodata
type(mct_gsMap) , pointer :: gsMap_i
Expand Down Expand Up @@ -565,9 +565,9 @@ subroutine ice_run_mct( EClock, cdata_i, x2i_i, i2x_i )
force_restart_now = seq_timemgr_RestartAlarmIsOn(EClock)

! if (calendar_type .eq. "GREGORIAN") then
! nyrp = nyr
! nyr = (curr_ymd/10000)+1 ! integer year of basedate
! if (nyr /= nyrp) then
! myearp = myear
! myear = (curr_ymd/10000)+1 ! integer year of basedate
! if (myear /= myearp) then
! new_year = .true.
! else
! new_year = .false.
Expand Down Expand Up @@ -617,7 +617,7 @@ subroutine ice_run_mct( EClock, cdata_i, x2i_i, i2x_i )
! check that internal clock is in sync with master clock
!--------------------------------------------------------------------

tod = sec
tod = msec
ymd = idate
if (.not. seq_timemgr_EClockDateInSync( EClock, ymd, tod )) then
call seq_timemgr_EClockGetData( EClock, curr_ymd=ymd_sync, &
Expand Down
2 changes: 1 addition & 1 deletion cicecore/drivers/mct/cesm1/ice_prescribed_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ module ice_prescribed_mod
use ice_blocks, only : nx_block, ny_block, block, get_block
use ice_domain, only : nblocks, distrb_info, blocks_ice
use ice_grid, only : TLAT,TLON,hm,tmask
use ice_calendar, only : idate, sec, calendar_type
use ice_calendar, only : idate, calendar_type
use ice_arrays_column, only : hin_max
use ice_read_write
use ice_exit, only: abort_ice
Expand Down
4 changes: 2 additions & 2 deletions cicecore/drivers/nuopc/cmeps/CICE_RunMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ subroutine ice_step

use ice_boundary, only: ice_HaloUpdate
use ice_calendar, only: dt, dt_dyn, ndtd, diagfreq, write_restart, istep
use ice_calendar, only: idate, sec
use ice_calendar, only: idate, msec
use ice_diagnostics, only: init_mass_diags, runtime_diags
use ice_diagnostics_bgc, only: hbrine_diags, zsal_diags, bgc_diags
use ice_domain, only: halo_info, nblocks
Expand Down Expand Up @@ -185,7 +185,7 @@ subroutine ice_step
if (prescribed_ice) then ! read prescribed ice
call t_barrierf('cice_run_presc_BARRIER',MPI_COMM_ICE)
call t_startf ('cice_run_presc')
call ice_prescribed_run(idate, sec)
call ice_prescribed_run(idate, msec)
call t_stopf ('cice_run_presc')
endif
#endif
Expand Down
22 changes: 11 additions & 11 deletions cicecore/drivers/nuopc/cmeps/ice_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,8 @@ module ice_comp_nuopc
use ice_grid , only : tlon, tlat, hm, tarea, ULON, ULAT
use ice_communicate , only : init_communicate, my_task, master_task, mpi_comm_ice
use ice_calendar , only : force_restart_now, write_ic
use ice_calendar , only : idate, mday, time, month, time2sec, year_init
use ice_calendar , only : sec, dt, calendar, calendar_type, nextsw_cday, istep
use ice_calendar , only : idate, mday, time, mmonth, time2sec, year_init
use ice_calendar , only : msec, dt, calendar, calendar_type, nextsw_cday, istep
use ice_kinds_mod , only : dbl_kind, int_kind, char_len, char_len_long
use ice_scam , only : scmlat, scmlon, single_column
use ice_fileunits , only : nu_diag, nu_diag_set, inst_index, inst_name
Expand Down Expand Up @@ -600,24 +600,24 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
call abort_ice(subname//' :: ERROR idate lt zero')
endif
iyear = (idate/10000) ! integer year of basedate
month = (idate-iyear*10000)/100 ! integer month of basedate
mday = idate-iyear*10000-month*100 ! day of month of basedate
mmonth= (idate-iyear*10000)/100 ! integer month of basedate
mday = idate-iyear*10000-mmonth*100 ! day of month of basedate

if (my_task == master_task) then
write(nu_diag,*) trim(subname),' curr_ymd = ',curr_ymd
write(nu_diag,*) trim(subname),' cice year_init = ',year_init
write(nu_diag,*) trim(subname),' cice start date = ',idate
write(nu_diag,*) trim(subname),' cice start ymds = ',iyear,month,mday,start_tod
write(nu_diag,*) trim(subname),' cice start ymds = ',iyear,mmonth,mday,start_tod
write(nu_diag,*) trim(subname),' cice calendar_type = ',trim(calendar_type)
endif

#ifdef CESMCOUPLED
if (calendar_type == "GREGORIAN" .or. &
calendar_type == "Gregorian" .or. &
calendar_type == "gregorian") then
call time2sec(iyear-(year_init-1),month,mday,time)
call time2sec(iyear-(year_init-1),mmonth,mday,time)
else
call time2sec(iyear-year_init,month,mday,time)
call time2sec(iyear-year_init,mmonth,mday,time)
endif
#endif
time = time+start_tod
Expand Down Expand Up @@ -878,7 +878,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
! TODO (mvertens, 2018-12-21): fill in iceberg_prognostic as .false.
if (debug_export > 0 .and. my_task==master_task) then
call State_fldDebug(exportState, flds_scalar_name, 'cice_export:', &
idate, sec, nu_diag, rc=rc)
idate, msec, nu_diag, rc=rc)
end if

!--------------------------------
Expand Down Expand Up @@ -1019,7 +1019,7 @@ subroutine ModelAdvance(gcomp, rc)
!--------------------------------

! cice clock
tod = sec
tod = msec
ymd = idate

! model clock
Expand Down Expand Up @@ -1080,7 +1080,7 @@ subroutine ModelAdvance(gcomp, rc)
! write Debug output
if (debug_import > 0 .and. my_task==master_task) then
call State_fldDebug(importState, flds_scalar_name, 'cice_import:', &
idate, sec, nu_diag, rc=rc)
idate, msec, nu_diag, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
end if
if (dbug > 0) then
Expand All @@ -1107,7 +1107,7 @@ subroutine ModelAdvance(gcomp, rc)
! write Debug output
if (debug_export > 0 .and. my_task==master_task) then
call State_fldDebug(exportState, flds_scalar_name, 'cice_export:', &
idate, sec, nu_diag, rc=rc)
idate, msec, nu_diag, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
end if
if (dbug > 0) then
Expand Down
2 changes: 1 addition & 1 deletion cicecore/drivers/nuopc/cmeps/ice_prescribed_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ end subroutine ice_prescribed_init
use ice_blocks , only : nx_block, ny_block, block, get_block
use ice_domain , only : nblocks, distrb_info, blocks_ice
use ice_grid , only : TLAT, TLON, hm, tmask, tarea, grid_type, ocn_gridcell_frac
use ice_calendar , only : idate, sec, calendar_type
use ice_calendar , only : idate, calendar_type
use ice_arrays_column , only : hin_max
use ice_read_write
use ice_exit , only: abort_ice
Expand Down

0 comments on commit 2378740

Please sign in to comment.