Skip to content

Commit

Permalink
Add restart_coszen namelist option (CICE-Consortium#480)
Browse files Browse the repository at this point in the history
* updated orbital calculations needed for cesm

* fixed problems in updated orbital calculations needed for cesm

* update CICE6 to support coupling with UFS

* put in changes so that both ufsatm and cesm requirements for potential temperature and density are satisfied

* update icepack submodule

* Revert "update icepack submodule"

This reverts commit e70d1ab.

* update comp_ice.backend with temporary ice_timers fix

* Fix threading problem in init_bgc

* Fix additional OMP problems

* changes for coldstart running

* Move the forapps directory

* remove cesmcoupled ifdefs

* Fix logging issues for NUOPC

* removal of many cpp-ifdefs

* fix compile errors

* fixes to get cesm working

* fixed white space issue

* Add restart_coszen namelist option

* Move restart_coszen to forcing_nml

* Update documentation on restart_coszen

Co-authored-by: Mariana Vertenstein <mvertens@ucar.edu>
Co-authored-by: apcraig <anthony.p.craig@gmail.com>
Co-authored-by: Denise Worthen <denise.worthen@noaa.gov>
  • Loading branch information
4 people authored Jul 17, 2020
1 parent ee5a0e9 commit b055c7f
Show file tree
Hide file tree
Showing 17 changed files with 385 additions and 632 deletions.
2 changes: 0 additions & 2 deletions cicecore/cicedynB/analysis/ice_history_shared.F90
Original file line number Diff line number Diff line change
Expand Up @@ -672,9 +672,7 @@ subroutine construct_filename(ncfile,suffix,ns)
iday = mday
isec = sec - dt

#ifdef CESMCOUPLED
if (write_ic) isec = sec
#endif
! construct filename
if (write_ic) then
write(ncfile,'(a,a,i4.4,a,i2.2,a,i2.2,a,i5.5,a,a)') &
Expand Down
7 changes: 5 additions & 2 deletions cicecore/cicedynB/general/ice_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ subroutine input_data
restart_pond_cesm, restart_pond_lvl, restart_pond_topo, restart_aero, &
restart_fsd, restart_iso
use ice_restart_shared, only: &
restart, restart_ext, restart_dir, restart_file, pointer_file, &
restart, restart_ext, restart_coszen, restart_dir, restart_file, pointer_file, &
runid, runtype, use_restart_time, restart_format, lcdf64
use ice_history_shared, only: hist_avg, history_dir, history_file, &
incond_dir, incond_file, version_name, &
Expand Down Expand Up @@ -212,7 +212,7 @@ subroutine input_data
oceanmixed_ice, restore_ice, restore_ocn, trestore, &
precip_units, default_season, wave_spec_type,nfreq, &
atm_data_type, ocn_data_type, bgc_data_type, fe_data_type, &
ice_data_type, wave_spec_file, &
ice_data_type, wave_spec_file, restart_coszen, &
fyear_init, ycycle, &
atm_data_dir, ocn_data_dir, bgc_data_dir, &
atm_data_format, ocn_data_format, rotate_wind, &
Expand Down Expand Up @@ -269,6 +269,7 @@ subroutine input_data
restart_dir = './' ! write to executable dir for default
restart_file = 'iced' ! restart file name prefix
restart_ext = .false. ! if true, read/write ghost cells
restart_coszen = .false. ! if true, read/write coszen
use_restart_time = .true. ! if true, use time info written in file
pointer_file = 'ice.restart_file'
restart_format = 'default' ! restart file format
Expand Down Expand Up @@ -563,6 +564,7 @@ subroutine input_data
call broadcast_scalar(restart, master_task)
call broadcast_scalar(restart_dir, master_task)
call broadcast_scalar(restart_ext, master_task)
call broadcast_scalar(restart_coszen, master_task)
call broadcast_scalar(use_restart_time, master_task)
call broadcast_scalar(restart_format, master_task)
call broadcast_scalar(lcdf64, master_task)
Expand Down Expand Up @@ -1458,6 +1460,7 @@ subroutine input_data
write(nu_diag,*) ' restart_dir = ', &
trim(restart_dir)
write(nu_diag,*) ' restart_ext = ', restart_ext
write(nu_diag,*) ' restart_coszen = ', restart_coszen
write(nu_diag,*) ' restart_format = ', &
trim(restart_format)
write(nu_diag,*) ' lcdf64 = ', &
Expand Down
17 changes: 5 additions & 12 deletions cicecore/cicedynB/infrastructure/ice_restart_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ module ice_restart_driver
field_loc_center, field_loc_NEcorner, &
field_type_scalar, field_type_vector
use ice_restart_shared, only: restart_dir, pointer_file, &
runid, use_restart_time, lenstr
runid, use_restart_time, lenstr, restart_coszen
use ice_restart
use ice_exit, only: abort_ice
use ice_fileunits, only: nu_diag, nu_rst_pointer, nu_restart, nu_dump
Expand Down Expand Up @@ -58,9 +58,7 @@ subroutine dumpfile(filename_spec)
stressp_1, stressp_2, stressp_3, stressp_4, &
stressm_1, stressm_2, stressm_3, stressm_4, &
stress12_1, stress12_2, stress12_3, stress12_4
#ifdef CESMCOUPLED
use ice_flux, only: coszen
#endif
use ice_state, only: aicen, vicen, vsnon, trcrn, uvel, vvel

character(len=char_len_long), intent(in), optional :: filename_spec
Expand Down Expand Up @@ -132,9 +130,9 @@ subroutine dumpfile(filename_spec)
!-----------------------------------------------------------------
! radiation fields
!-----------------------------------------------------------------
#ifdef CESMCOUPLED
call write_restart_field(nu_dump,0,coszen,'ruf8','coszen',1,diag)
#endif
if (restart_coszen) call write_restart_field(nu_dump,0,coszen,'ruf8','coszen',1,diag)

call write_restart_field(nu_dump,0,scale_factor,'ruf8','scale_factor',1,diag)

call write_restart_field(nu_dump,0,swvdr,'ruf8','swvdr',1,diag)
Expand Down Expand Up @@ -209,9 +207,7 @@ subroutine restartfile (ice_ic)
stressp_1, stressp_2, stressp_3, stressp_4, &
stressm_1, stressm_2, stressm_3, stressm_4, &
stress12_1, stress12_2, stress12_3, stress12_4
#ifdef CESMCOUPLED
use ice_flux, only: coszen
#endif
use ice_grid, only: tmask, grid_type
use ice_state, only: trcr_depend, aice, vice, vsno, trcr, &
aice0, aicen, vicen, vsnon, trcrn, aice_init, uvel, vvel, &
Expand Down Expand Up @@ -310,11 +306,8 @@ subroutine restartfile (ice_ic)
if (my_task == master_task) &
write(nu_diag,*) 'radiation fields'

#ifdef CESMCOUPLED
call read_restart_field(nu_restart,0,coszen,'ruf8', &
! 'coszen',1,diag, field_loc_center, field_type_scalar)
if (restart_coszen) call read_restart_field(nu_restart,0,coszen,'ruf8', &
'coszen',1,diag)
#endif
call read_restart_field(nu_restart,0,scale_factor,'ruf8', &
'scale_factor',1,diag, field_loc_center, field_type_scalar)
call read_restart_field(nu_restart,0,swvdr,'ruf8', &
Expand Down
8 changes: 3 additions & 5 deletions cicecore/cicedynB/infrastructure/io/io_netcdf/ice_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ module ice_restart
use netcdf
use ice_restart_shared, only: &
restart_ext, restart_dir, restart_file, pointer_file, &
runid, use_restart_time, lcdf64, lenstr
runid, use_restart_time, lcdf64, lenstr, restart_coszen
use ice_fileunits, only: nu_diag, nu_rst_pointer
use ice_exit, only: abort_ice
use icepack_intfc, only: icepack_query_parameters
Expand Down Expand Up @@ -84,7 +84,6 @@ subroutine init_restart_read(ice_ic)
endif
endif ! use namelist values if use_restart_time = F

write(nu_diag,*) 'Restart read at istep=',istep0,time,time_forc
endif

call broadcast_scalar(istep0,master_task)
Expand Down Expand Up @@ -227,10 +226,9 @@ subroutine init_restart_write(filename_spec)

call define_rest_field(ncid,'uvel',dims)
call define_rest_field(ncid,'vvel',dims)

if (restart_coszen) call define_rest_field(ncid,'coszen',dims)

#ifdef CESMCOUPLED
call define_rest_field(ncid,'coszen',dims)
#endif
call define_rest_field(ncid,'scale_factor',dims)
call define_rest_field(ncid,'swvdr',dims)
call define_rest_field(ncid,'swvdf',dims)
Expand Down
8 changes: 3 additions & 5 deletions cicecore/cicedynB/infrastructure/io/io_pio2/ice_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,8 @@ module ice_restart
use ice_kinds_mod
use ice_restart_shared, only: &
restart, restart_ext, restart_dir, restart_file, pointer_file, &
runid, runtype, use_restart_time, restart_format, lcdf64, lenstr
runid, runtype, use_restart_time, restart_format, lcdf64, lenstr, &
restart_coszen
use ice_pio
use pio
use icepack_intfc, only: icepack_warnings_flush, icepack_warnings_aborted
Expand Down Expand Up @@ -245,10 +246,7 @@ subroutine init_restart_write(filename_spec)

call define_rest_field(File,'uvel',dims)
call define_rest_field(File,'vvel',dims)

#ifdef CESMCOUPLED
call define_rest_field(File,'coszen',dims)
#endif
if (restart_coszen) call define_rest_field(File,'coszen',dims)
call define_rest_field(File,'scale_factor',dims)
call define_rest_field(File,'swvdr',dims)
call define_rest_field(File,'swvdf',dims)
Expand Down
81 changes: 18 additions & 63 deletions cicecore/drivers/nuopc/cmeps/CICE_InitMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,40 +25,21 @@ module CICE_InitMod

implicit none
private
public :: CICE_Initialize, cice_init
public :: cice_init

!=======================================================================

contains

!=======================================================================

! Initialize the basic state, grid and all necessary parameters for
! running the CICE model. Return the initial state in routine
! export state.
! Note: This initialization driver is designed for standalone and
! CESM-coupled applications. For other
! applications (e.g., standalone CAM), this driver would be
! replaced by a different driver that calls subroutine cice_init,
! where most of the work is done.

subroutine CICE_Initialize

character(len=*), parameter :: subname='(CICE_Initialize)'
!--------------------------------------------------------------------
! model initialization
!--------------------------------------------------------------------

call cice_init

end subroutine CICE_Initialize

!=======================================================================
!
! Initialize CICE model.

subroutine cice_init

! Initialize the basic state, grid and all necessary parameters for
! running the CICE model.

use ice_arrays_column, only: hin_max, c_hi_range, alloc_arrays_column
use ice_arrays_column, only: floe_rad_l, floe_rad_c, &
floe_binwidth, c_fsd_range
Expand All @@ -74,8 +55,7 @@ subroutine cice_init
use ice_dyn_shared, only: kdyn, init_evp, alloc_dyn_shared
use ice_flux, only: init_coupler_flux, init_history_therm, &
init_history_dyn, init_flux_atm, init_flux_ocn, alloc_flux
use ice_forcing, only: init_forcing_ocn, init_forcing_atmo, &
get_forcing_atmo, get_forcing_ocn, get_wave_spec
use ice_forcing, only: init_forcing_ocn
use ice_forcing_bgc, only: get_forcing_bgc, get_atm_bgc, &
faero_default, faero_optics, alloc_forcing_bgc, fiso_default
use ice_grid, only: init_grid1, init_grid2, alloc_grid
Expand All @@ -87,9 +67,6 @@ subroutine cice_init
use ice_restoring, only: ice_HaloRestore_init
use ice_timers, only: timer_total, init_ice_timers, ice_timer_start
use ice_transport_driver, only: init_transport
#ifdef popcice
use drv_forcing, only: sst_sss
#endif

logical(kind=log_kind) :: tr_aero, tr_zaero, skl_bgc, z_tracers, &
tr_iso, tr_fsd, wave_spec
Expand Down Expand Up @@ -129,10 +106,6 @@ subroutine cice_init
endif

call init_coupler_flux ! initialize fluxes exchanged with coupler

#ifdef popcice
call sst_sss ! POP data for CICE initialization
#endif
call init_thermo_vertical ! initialize vertical thermodynamics

call icepack_init_itd(ncat=ncat, hin_max=hin_max) ! ice thickness distribution
Expand All @@ -158,7 +131,9 @@ subroutine cice_init

call calendar(time) ! determine the initial date

! TODO: - why is this being called when you are using CMEPS?
call init_forcing_ocn(dt) ! initialize sss and sst from data

call init_state ! initialize the ice state
call init_transport ! initialize horizontal transport
call ice_HaloRestore_init ! restored boundary conditions
Expand All @@ -182,51 +157,31 @@ subroutine cice_init
if (icepack_warnings_aborted()) call abort_ice(trim(subname), &
file=__FILE__,line= __LINE__)

if (tr_aero .or. tr_zaero) call faero_optics !initialize aerosol optical
!property tables
if (tr_aero .or. tr_zaero) then
call faero_optics !initialize aerosol optical property tables
end if

! Initialize shortwave components using swdn from previous timestep
! if restarting. These components will be scaled to current forcing
! in prep_radiation.
if (trim(runtype) == 'continue' .or. restart) &
call init_shortwave ! initialize radiative transfer

! istep = istep + 1 ! update time step counters
! istep1 = istep1 + 1
! time = time + dt ! determine the time and date
! call calendar(time) ! at the end of the first timestep

!--------------------------------------------------------------------
! coupler communication or forcing data initialization
!--------------------------------------------------------------------

#ifndef coupled
call init_forcing_atmo ! initialize atmospheric forcing (standalone)
if (trim(runtype) == 'continue' .or. restart) then
call init_shortwave ! initialize radiative transfer
end if

#ifndef CESMCOUPLED
if (tr_fsd .and. wave_spec) call get_wave_spec ! wave spectrum in ice
call get_forcing_atmo ! atmospheric forcing from data
call get_forcing_ocn(dt) ! ocean forcing from data
!--------------------------------------------------------------------
! coupler communication or forcing data initialization
!--------------------------------------------------------------------

! isotopes
if (tr_iso) call fiso_default ! default values
! aerosols
! if (tr_aero) call faero_data ! data file
! if (tr_zaero) call fzaero_data ! data file (gx1)
if (tr_aero .or. tr_zaero) call faero_default ! default values
if (skl_bgc .or. z_tracers) call get_forcing_bgc ! biogeochemistry
#endif
#endif
if (z_tracers) call get_atm_bgc ! biogeochemistry

if (runtype == 'initial' .and. .not. restart) &
if (runtype == 'initial' .and. .not. restart) then
call init_shortwave ! initialize radiative transfer using current swdn
end if

call init_flux_atm ! initialize atmosphere fluxes sent to coupler
call init_flux_ocn ! initialize ocean fluxes sent to coupler

! if (write_ic) call accum_hist(dt) ! write initial conditions

end subroutine cice_init

!=======================================================================
Expand Down
50 changes: 11 additions & 39 deletions cicecore/drivers/nuopc/cmeps/CICE_RunMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,7 @@
module CICE_RunMod

use ice_kinds_mod
#ifdef CESMCOUPLED
use perf_mod, only : t_startf, t_stopf, t_barrierf
#endif
use cice_wrapper_mod, only : t_startf, t_stopf, t_barrierf
use ice_fileunits, only: nu_diag
use ice_arrays_column, only: oceanmixed_ice
use ice_constants, only: c0, c1
Expand Down Expand Up @@ -79,48 +77,22 @@ subroutine CICE_Run
! timestep loop
!--------------------------------------------------------------------

! timeLoop: do

! call ice_step

istep = istep + 1 ! update time step counters
istep1 = istep1 + 1
time = time + dt ! determine the time and date

! call calendar(time) ! at the end of the timestep
istep = istep + 1 ! update time step counters
istep1 = istep1 + 1
time = time + dt ! determine the time and date

call ice_timer_start(timer_couple) ! atm/ocn coupling

#ifndef coupled
#ifndef CESMCOUPLED
! for now, wave_spectrum is constant in time
! if (tr_fsd .and. wave_spec) call get_wave_spec ! wave spectrum in ice
call get_forcing_atmo ! atmospheric forcing from data
call get_forcing_ocn(dt) ! ocean forcing from data

! isotopes
if (tr_iso) call fiso_default ! default values
! aerosols
! if (tr_aero) call faero_data ! data file
! if (tr_zaero) call fzaero_data ! data file (gx1)
if (tr_aero .or. tr_zaero) call faero_default ! default values

if (skl_bgc .or. z_tracers) call get_forcing_bgc ! biogeochemistry
#endif
#endif
if (z_tracers) call get_atm_bgc ! biogeochemistry
call ice_timer_start(timer_couple) ! atm/ocn coupling

call init_flux_atm ! Initialize atmosphere fluxes sent to coupler
call init_flux_ocn ! initialize ocean fluxes sent to coupler
if (z_tracers) call get_atm_bgc ! biogeochemistry

call calendar(time) ! at the end of the timestep
call init_flux_atm ! Initialize atmosphere fluxes sent to coupler
call init_flux_ocn ! initialize ocean fluxes sent to coupler

call ice_timer_stop(timer_couple) ! atm/ocn coupling
call calendar(time) ! at the end of the timestep

call ice_step
call ice_timer_stop(timer_couple) ! atm/ocn coupling

! if (stop_now >= 1) exit timeLoop
! enddo timeLoop
call ice_step

!--------------------------------------------------------------------
! end of timestep loop
Expand Down
Loading

0 comments on commit b055c7f

Please sign in to comment.