Skip to content

Commit

Permalink
Get bgc code running on 4 compilers on conrad.
Browse files Browse the repository at this point in the history
Update history field control, place control logicals inside init and accum subroutines for consistency.

Fix some indent issues in history subroutines.

Comment out OMP loop that was causing problems on conrad_cray.

Fix intent inout arguments in ice_forcing_bgc.F90, init_bgc_data for fed1, fep1.

Modify ice_arrays_column so more variables are dynamically allocated using icepack query routines.
  • Loading branch information
apcraig committed Oct 26, 2018
1 parent acbd01a commit 85cdedb
Show file tree
Hide file tree
Showing 10 changed files with 646 additions and 521 deletions.
21 changes: 10 additions & 11 deletions cicecore/cicedynB/analysis/ice_history.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1408,13 +1408,12 @@ subroutine init_hist (dt)
call init_hist_mechred_2D

! melt ponds
if (tr_pond) call init_hist_pond_2D
call init_hist_pond_2D

! biogeochemistry
if (tr_aero .or. tr_brine .or. solve_zsal .or. skl_bgc) &
call init_hist_bgc_2D
call init_hist_bgc_2D

if (formdrag) call init_hist_drag_2D
call init_hist_drag_2D

!-----------------------------------------------------------------
! 3D (category) variables looped separately for ordering
Expand Down Expand Up @@ -1486,10 +1485,10 @@ subroutine init_hist (dt)
call init_hist_mechred_3Dc

! melt ponds
if (tr_pond) call init_hist_pond_3Dc
call init_hist_pond_3Dc

! biogeochemistry
if (tr_brine) call init_hist_bgc_3Dc
call init_hist_bgc_3Dc

!-----------------------------------------------------------------
! 3D (vertical) variables must be looped separately
Expand All @@ -1506,8 +1505,8 @@ subroutine init_hist (dt)
! endif ! if (histfreq(ns1) /= 'x') then
! enddo ! ns1

if (z_tracers .or. solve_zsal) call init_hist_bgc_3Db
if (z_tracers) call init_hist_bgc_3Da
call init_hist_bgc_3Db
call init_hist_bgc_3Da

!-----------------------------------------------------------------
! 4D (categories, vertical) variables must be looped separately
Expand Down Expand Up @@ -2977,13 +2976,13 @@ subroutine accum_hist (dt)
call accum_hist_mechred (iblk)

! melt ponds
if (tr_pond) call accum_hist_pond (iblk)
call accum_hist_pond (iblk)

! biogeochemistry
if (tr_aero .or. tr_brine .or. skl_bgc) call accum_hist_bgc (iblk)
call accum_hist_bgc (iblk)

! form drag
if (formdrag) call accum_hist_drag (iblk)
call accum_hist_drag (iblk)

enddo ! iblk
!$OMP END PARALLEL DO
Expand Down
1,000 changes: 526 additions & 474 deletions cicecore/cicedynB/analysis/ice_history_bgc.F90

Large diffs are not rendered by default.

27 changes: 24 additions & 3 deletions cicecore/cicedynB/analysis/ice_history_drag.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,10 @@ module ice_history_drag
use ice_domain_size, only: max_nstrm
use ice_constants, only: c0, c1
use ice_fileunits, only: nu_nml, nml_filename, &
get_fileunit, release_fileunit
get_fileunit, release_fileunit, nu_diag
use ice_exit, only: abort_ice
use icepack_intfc, only: icepack_warnings_flush, icepack_warnings_aborted
use icepack_intfc, only: icepack_warnings_flush, icepack_warnings_aborted, &
icepack_query_parameters

implicit none
private
Expand Down Expand Up @@ -66,8 +67,14 @@ subroutine init_hist_drag_2D

integer (kind=int_kind) :: ns
integer (kind=int_kind) :: nml_error ! namelist i/o error flag
logical (kind=log_kind) :: formdrag
character(len=*), parameter :: subname = '(init_hist_drag_2D)'

call icepack_query_parameters(formdrag_out=formdrag)
call icepack_warnings_flush(nu_diag)
if (icepack_warnings_aborted()) call abort_ice(error_message=subname, &
file=__FILE__, line=__LINE__)

!-----------------------------------------------------------------
! read namelist
!-----------------------------------------------------------------
Expand Down Expand Up @@ -98,6 +105,8 @@ subroutine init_hist_drag_2D
call broadcast_scalar (f_Cdn_ocn, master_task)
call broadcast_scalar (f_drag, master_task)

if (formdrag) then

! 2D variables

do ns = 1, nstreams
Expand Down Expand Up @@ -220,6 +229,8 @@ subroutine init_hist_drag_2D

enddo ! nstreams

endif ! formdrag

end subroutine init_hist_drag_2D

!=======================================================================
Expand All @@ -236,13 +247,21 @@ subroutine accum_hist_drag (iblk)

integer (kind=int_kind), intent(in) :: &
iblk ! block index
logical (kind=log_kind) :: formdrag
character(len=*), parameter :: subname = '(accum_hist_drag)'

!---------------------------------------------------------------
! increment field
!---------------------------------------------------------------

! 2D fields
call icepack_query_parameters(formdrag_out=formdrag)
call icepack_warnings_flush(nu_diag)
if (icepack_warnings_aborted()) call abort_ice(error_message=subname, &
file=__FILE__, line=__LINE__)

if (formdrag) then

! 2D fields

if (f_Cdn_atm (1:1) /= 'x') &
call accum_hist_field(n_Cdn_atm, iblk, Cdn_atm(:,:,iblk), a2D)
Expand Down Expand Up @@ -275,6 +294,8 @@ subroutine accum_hist_drag (iblk)
iblk, Cdn_ocn_skin(:,:,iblk), a2D)
end if

endif ! formdrag

end subroutine accum_hist_drag

!=======================================================================
Expand Down
14 changes: 14 additions & 0 deletions cicecore/cicedynB/analysis/ice_history_pond.F90
Original file line number Diff line number Diff line change
Expand Up @@ -131,6 +131,8 @@ subroutine init_hist_pond_2D
call broadcast_scalar (f_ipond_ai, master_task)
call broadcast_scalar (f_apeff_ai, master_task)

if (tr_pond) then

! 2D variables
do ns = 1, nstreams

Expand Down Expand Up @@ -183,6 +185,8 @@ subroutine init_hist_pond_2D
ns, f_apeff_ai)

enddo ! nstreams

endif ! tr_pond

end subroutine init_hist_pond_2D

Expand All @@ -194,7 +198,15 @@ subroutine init_hist_pond_3Dc
use ice_history_shared, only: tstr3Dc, tcstr, define_hist_field

integer (kind=int_kind) :: ns
logical (kind=log_kind) :: tr_pond
character(len=*), parameter :: subname = '(init_hist_pond_3Dc)'

call icepack_query_tracer_flags(tr_pond_out=tr_pond)
call icepack_warnings_flush(nu_diag)
if (icepack_warnings_aborted()) call abort_ice(error_message=subname, &
file=__FILE__, line=__LINE__)

if (tr_pond) then

! 3D (category) variables must be looped separately
do ns = 1, nstreams
Expand All @@ -217,6 +229,8 @@ subroutine init_hist_pond_3Dc

enddo ! ns

endif ! tr_pond

end subroutine init_hist_pond_3Dc

!=======================================================================
Expand Down
9 changes: 6 additions & 3 deletions cicecore/cicedynB/dynamics/ice_transport_remap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -464,8 +464,10 @@ subroutine horizontal_remap (dt, ntrace, &
!---! Remap the open water area (without tracers).
!---!-------------------------------------------------------------------

!$OMP PARALLEL DO PRIVATE(iblk,ilo,ihi,jlo,jhi,this_block,n,m, &
!$OMP indxinc,indxjnc,mmask,tmask,istop,jstop,l_stop)
!--- tcraig, tcx, this omp loop leads to a seg fault in gnu
!--- need to check private variables and debug further
!$TCXOMP PARALLEL DO PRIVATE(iblk,ilo,ihi,jlo,jhi,this_block,n,m, &
!$TCXOMP indxinc,indxjnc,mmask,tmask,istop,jstop,l_stop)
do iblk = 1, nblocks

l_stop = .false.
Expand Down Expand Up @@ -566,7 +568,7 @@ subroutine horizontal_remap (dt, ntrace, &
endif

enddo ! iblk
!$OMP END PARALLEL DO
!$TCXOMP END PARALLEL DO

!-------------------------------------------------------------------
! Ghost cell updates
Expand Down Expand Up @@ -992,6 +994,7 @@ subroutine make_masks (nx_block, ny_block, &
if (present(tm)) then

tmask(:,:,:,n) = c0

do nt = 1, ntrace
if (has_dependents(nt)) then
do ij = 1, icells(n)
Expand Down
2 changes: 1 addition & 1 deletion cicecore/cicedynB/general/ice_forcing_bgc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -771,7 +771,7 @@ subroutine init_bgc_data (fed1,fep1)
use netcdf
#endif

real (kind=dbl_kind), dimension(nx_block, ny_block, max_blocks), intent(out) :: &
real (kind=dbl_kind), dimension(nx_block, ny_block, max_blocks), intent(inout) :: &
fed1, & ! first dissolved iron pool (nM)
fep1 ! first particulate iron pool (nM)

Expand Down
1 change: 0 additions & 1 deletion cicecore/cicedynB/general/ice_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -603,7 +603,6 @@ subroutine input_data
call broadcast_scalar(restart_pond_lvl, master_task)
call broadcast_scalar(tr_pond_topo, master_task)
call broadcast_scalar(restart_pond_topo, master_task)
call broadcast_scalar(tr_pond, master_task)
call broadcast_scalar(tr_aero, master_task)
call broadcast_scalar(restart_aero, master_task)
call broadcast_scalar(ncat, master_task)
Expand Down
2 changes: 1 addition & 1 deletion cicecore/cicedynB/general/ice_step_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1169,7 +1169,7 @@ subroutine biogeochemistry (dt, iblk)
fep(i,j,:,iblk), zaeros(i,j,:,iblk), &
ocean_bio_all(i,j,:,iblk), &
hum(i,j, iblk))

do mm = 1,nbtrcr
ocean_bio(i,j,mm,iblk) = ocean_bio_all(i,j,bio_index_o(mm),iblk)
enddo ! mm
Expand Down
3 changes: 3 additions & 0 deletions cicecore/drivers/cice/CICE_InitMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,9 @@ subroutine cice_init
call init_communicate ! initial setup for message passing
call init_fileunits ! unit numbers

! tcx debug, this will create a different logfile for each pe
! if (my_task /= master_task) nu_diag = 100+my_task

call icepack_configure() ! initialize icepack
call icepack_warnings_flush(nu_diag)
if (icepack_warnings_aborted()) call abort_ice(trim(subname), &
Expand Down
Loading

0 comments on commit 85cdedb

Please sign in to comment.