Skip to content

Commit

Permalink
removal of many cpp-ifdefs
Browse files Browse the repository at this point in the history
  • Loading branch information
Mariana Vertenstein committed Jul 4, 2020
1 parent 6bccf71 commit b4afd2e
Show file tree
Hide file tree
Showing 6 changed files with 249 additions and 316 deletions.
84 changes: 19 additions & 65 deletions cicecore/drivers/nuopc/cmeps/CICE_InitMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,57 +25,37 @@ 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(mpicom_ice)

! 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
use ice_state, only: alloc_state
use ice_flux_bgc, only: alloc_flux_bgc
use ice_calendar, only: dt, dt_dyn, time, istep, istep1, write_ic, &
init_calendar, calendar
use ice_communicate, only: init_communicate, my_task, master_task
use ice_communicate, only: my_task, master_task
use ice_diagnostics, only: init_diags
use ice_domain, only: init_domain_blocks
use ice_domain_size, only: ncat, nfsd
use ice_dyn_eap, only: init_eap, alloc_dyn_eap
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(mpicom_ice)
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

integer (kind=int_kind), optional, intent(in) :: &
mpicom_ice ! communicator for sequential ccsm
Expand All @@ -98,7 +75,6 @@ subroutine cice_init(mpicom_ice)
tr_iso, tr_fsd, wave_spec
character(len=*), parameter :: subname = '(cice_init)'

call init_communicate(mpicom_ice) ! initial setup for message passing
call init_fileunits ! unit numbers

call icepack_configure() ! initialize icepack
Expand Down Expand Up @@ -133,10 +109,6 @@ subroutine cice_init(mpicom_ice)
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 @@ -162,7 +134,9 @@ subroutine cice_init(mpicom_ice)

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 @@ -186,51 +160,31 @@ subroutine cice_init(mpicom_ice)
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
36 changes: 36 additions & 0 deletions cicecore/drivers/nuopc/cmeps/cice_wrapper_mod.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
module cice_wrapper_mod

#ifdef CESMCOUPLED
use perf_mod, only : t_startf, t_stopf, t_barrierf
#endif


contains

#ifndef CESMCOUPLED
! These are just stub routines put in place to remove

subroutine shr_file_setLogUnit(nunit)
integer, intent(in) :: nunit
! do nothing for this stub - its just here to replace
! having cppdefs in the main program
end subroutine shr_file_setLogUnit
subroutine shr_file_getLogUnit(nunit)
integer, intent(in) :: nunit
! do nothing for this stub - its just here to replace
! having cppdefs in the main program
end subroutine shr_file_getLogUnit

subroutine t_startf(string)
character(len=*) :: string
end subroutine t_startf
subroutine t_stopf(string)
character(len=*) :: string
end subroutine t_stopf
subroutine t_barrierf(string, comm)
character(len=*) :: string
integer:: comm
end subroutine t_barrierf
#endif

end module cice_wrapper_mod
Loading

0 comments on commit b4afd2e

Please sign in to comment.