Skip to content

Commit

Permalink
Remove redundant turns arguments
Browse files Browse the repository at this point in the history
WIP...
  • Loading branch information
marshallward committed Jan 17, 2025
1 parent 14f2c97 commit 33a6c0e
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 28 deletions.
19 changes: 15 additions & 4 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@ module MOM
use MOM_checksum_packages, only : MOM_thermo_chksum, MOM_state_chksum
use MOM_checksum_packages, only : MOM_accel_chksum, MOM_surface_chksum
use MOM_coms, only : num_PEs
use MOM_coupler_types, only : coupler_type_initialized
use MOM_coupler_types, only : coupler_type_spawn
use MOM_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end
use MOM_cpu_clock, only : CLOCK_COMPONENT, CLOCK_SUBCOMPONENT
use MOM_cpu_clock, only : CLOCK_MODULE_DRIVER, CLOCK_MODULE, CLOCK_ROUTINE
Expand Down Expand Up @@ -3735,8 +3737,7 @@ subroutine extract_surface_state(CS, sfc_state_in)
if (associated(CS%frac_shelf_h)) use_iceshelves = .true.

turns = 0
if (CS%rotate_index) &
turns = G%HI%turns
if (CS%rotate_index) turns = G%HI%turns

if (.not.sfc_state_in%arrays_allocated) then
! Consider using a run-time flag to determine whether to do the vertical
Expand All @@ -3749,8 +3750,18 @@ subroutine extract_surface_state(CS, sfc_state_in)
if (CS%rotate_index) then
allocate(sfc_state)
call allocate_surface_state(sfc_state, G, use_temperature, &
do_integrals=.true., omit_frazil=.not.associated(CS%tv%frazil),&
use_iceshelves=use_iceshelves, sfc_state_in=sfc_state_in, turns=turns)
do_integrals=.true., omit_frazil=.not.associated(CS%tv%frazil), &
use_iceshelves=use_iceshelves &
)

! Coupler types use the input grid.
if (coupler_type_initialized(sfc_state_in%tr_fields)) then
call coupler_type_spawn(sfc_state_in%tr_fields, sfc_state%tr_fields, &
[G_in%isc, G_in%isc, G_in%iec, G_in%iec], &
[G_in%jsc, G_in%jsc, G_in%jec, G_in%jec], &
as_needed=.true. &
)
endif
else
sfc_state => sfc_state_in
endif
Expand Down
56 changes: 32 additions & 24 deletions src/core/MOM_variables.F90
Original file line number Diff line number Diff line change
Expand Up @@ -338,7 +338,8 @@ module MOM_variables
!! the ocean model. Unused fields are unallocated.
subroutine allocate_surface_state(sfc_state, G, use_temperature, do_integrals, &
gas_fields_ocn, use_meltpot, use_iceshelves, &
omit_frazil, sfc_state_in, turns)
!omit_frazil, sfc_state_in, turns)
omit_frazil)
type(ocean_grid_type), intent(in) :: G !< ocean grid structure
type(surface), intent(inout) :: sfc_state !< ocean surface state type to be allocated.
logical, optional, intent(in) :: use_temperature !< If true, allocate the space for thermodynamic variables.
Expand All @@ -355,15 +356,15 @@ subroutine allocate_surface_state(sfc_state, G, use_temperature, do_integrals, &
!! under ice shelves.
logical, optional, intent(in) :: omit_frazil !< If present and false, do not allocate the space to
!! pass frazil fluxes to the coupler
type(surface), &
optional, intent(in) :: sfc_state_in !< If present and its tr_fields are initialized,
!! this type describes the ocean and surface-ice fields that
!! will participate in the calculation of additional gas or
!! other tracer fluxes, and can be used to spawn related
!! internal variables in the ice model. If gas_fields_ocn
!! is present, it is used and tr_fields_in is ignored.
integer, optional, intent(in) :: turns !< If present, the number of counterclockwise quarter
!! turns to use on the new grid.
!!type(surface), &
!! optional, intent(in) :: sfc_state_in !< If present and its tr_fields are initialized,
!! !! this type describes the ocean and surface-ice fields that
!! !! will participate in the calculation of additional gas or
!! !! other tracer fluxes, and can be used to spawn related
!! !! internal variables in the ice model. If gas_fields_ocn
!! !! is present, it is used and tr_fields_in is ignored.
!!integer, optional, intent(in) :: turns !< If present, the number of counterclockwise quarter
!! !! turns to use on the new grid.

! local variables
logical :: use_temp, alloc_integ, use_melt_potential, alloc_iceshelves, alloc_frazil
Expand Down Expand Up @@ -416,21 +417,27 @@ subroutine allocate_surface_state(sfc_state, G, use_temperature, do_integrals, &
allocate(sfc_state%tauy_shelf(isd:ied,JsdB:JedB), source=0.0)
endif

! The data fields in the coupler_2d_bc_type are never rotated.
even_turns = .true. ; if (present(turns)) even_turns = (modulo(turns, 2) == 0)
if (even_turns) then
tr_field_i_mem(1:4) = (/is,is,ie,ie/) ; tr_field_j_mem(1:4) = (/js,js,je,je/)
else
tr_field_i_mem(1:4) = (/js,js,je,je/) ; tr_field_j_mem(1:4) = (/is,is,ie,ie/)
endif
!! The data fields in the coupler_2d_bc_type are never rotated.
!!even_turns = .true.
!!if (present(turns)) even_turns = (modulo(turns, 2) == 0)
!even_turns = modulo(G%HI%turns, 2) == 0

!if (even_turns) then
! tr_field_i_mem(:) = [is, is, ie, ie]
! tr_field_j_mem(:) = [js, js, je, je]
!else
! tr_field_i_mem(:) = [js, js, je, je]
! tr_field_j_mem(:) = [is, is, ie, ie]
!endif
if (present(gas_fields_ocn)) then
call coupler_type_spawn(gas_fields_ocn, sfc_state%tr_fields, &
tr_field_i_mem, tr_field_j_mem, as_needed=.true.)
elseif (present(sfc_state_in)) then
if (coupler_type_initialized(sfc_state_in%tr_fields)) then
call coupler_type_spawn(sfc_state_in%tr_fields, sfc_state%tr_fields, &
tr_field_i_mem, tr_field_j_mem, as_needed=.true.)
endif
!tr_field_i_mem, tr_field_j_mem, as_needed=.true.)
[is,is,ie,ie], [js,js,je,je], as_needed=.true.)
!elseif (present(sfc_state_in)) then
! if (coupler_type_initialized(sfc_state_in%tr_fields)) then
! call coupler_type_spawn(sfc_state_in%tr_fields, sfc_state%tr_fields, &
! tr_field_i_mem, tr_field_j_mem, as_needed=.true.)
! endif
endif

sfc_state%arrays_allocated = .true.
Expand Down Expand Up @@ -480,7 +487,8 @@ subroutine rotate_surface_state(sfc_state_in, sfc_state, G, turns)
if (.not. sfc_state%arrays_allocated) then
call allocate_surface_state(sfc_state, G, use_temperature=use_temperature, &
do_integrals=do_integrals, use_meltpot=use_melt_potential, &
use_iceshelves=use_iceshelves, sfc_state_in=sfc_state_in, turns=turns)
!use_iceshelves=use_iceshelves, sfc_state_in=sfc_state_in, turns=turns)
use_iceshelves=use_iceshelves)
endif

if (use_temperature) then
Expand Down

0 comments on commit 33a6c0e

Please sign in to comment.