Skip to content

Commit

Permalink
Merge pull request #1108 from Hallberg-NOAA/array_syntax_cleanup
Browse files Browse the repository at this point in the history
MOM6: +Corrected the use of array syntax calculations
  • Loading branch information
marshallward authored May 12, 2020
2 parents 70cfd64 + b2453e4 commit 3e7766a
Show file tree
Hide file tree
Showing 8 changed files with 215 additions and 214 deletions.
19 changes: 8 additions & 11 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1013,7 +1013,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
Time_local + real_to_time(US%T_to_s*(bbl_time_int-dt)), CS%diag)
! Calculate the BBL properties and store them inside visc (u,h).
call cpu_clock_begin(id_clock_BBL_visc)
call set_viscous_BBL(CS%u(:,:,:), CS%v(:,:,:), CS%h, CS%tv, CS%visc, G, GV, US, &
call set_viscous_BBL(CS%u, CS%v, CS%h, CS%tv, CS%visc, G, GV, US, &
CS%set_visc_CSp, symmetrize=.true.)
call cpu_clock_end(id_clock_BBL_visc)
if (showCallTree) call callTree_wayPoint("done with set_viscous_BBL (step_MOM)")
Expand Down Expand Up @@ -2204,7 +2204,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
allocate(CS%tv%frazil(isd:ied,jsd:jed)) ; CS%tv%frazil(:,:) = 0.0
endif
if (bound_salinity) then
allocate(CS%tv%salt_deficit(isd:ied,jsd:jed)) ; CS%tv%salt_deficit(:,:)=0.0
allocate(CS%tv%salt_deficit(isd:ied,jsd:jed)) ; CS%tv%salt_deficit(:,:) = 0.0
endif

if (bulkmixedlayer .or. use_temperature) then
Expand Down Expand Up @@ -2369,20 +2369,17 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &

if (associated(sponge_in_CSp)) then
! TODO: Implementation and testing of non-ALE spong rotation
call MOM_error(FATAL, "Index rotation of non-ALE sponge is not yet " &
// "implemented.")
call MOM_error(FATAL, "Index rotation of non-ALE sponge is not yet implemented.")
endif

if (associated(ALE_sponge_in_CSp)) then
call rotate_ALE_sponge(ALE_sponge_in_CSp, G_in, CS%ALE_sponge_CSp, G, &
turns, param_file)
call update_ALE_sponge_field(CS%ALE_sponge_CSp, T_in, CS%T)
call update_ALE_sponge_field(CS%ALE_sponge_CSp, S_in, CS%S)
call rotate_ALE_sponge(ALE_sponge_in_CSp, G_in, CS%ALE_sponge_CSp, G, turns, param_file)
call update_ALE_sponge_field(CS%ALE_sponge_CSp, T_in, G, GV, CS%T)
call update_ALE_sponge_field(CS%ALE_sponge_CSp, S_in, G, GV, CS%S)
endif

if (associated(OBC_in)) &
call rotate_OBC_init(OBC_in, G, GV, US, param_file, CS%tv, restart_CSp, &
CS%OBC)
call rotate_OBC_init(OBC_in, G, GV, US, param_file, CS%tv, restart_CSp, CS%OBC)

deallocate(u_in)
deallocate(v_in)
Expand Down Expand Up @@ -2427,7 +2424,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
G => CS%G
if (CS%debug .or. CS%G%symmetric) then
call clone_MOM_domain(CS%G%Domain, CS%G%Domain_aux, symmetric=.false.)
else ; CS%G%Domain_aux => CS%G%Domain ;endif
else ; CS%G%Domain_aux => CS%G%Domain ; endif
G%ke = GV%ke
endif

Expand Down
20 changes: 11 additions & 9 deletions src/ice_shelf/MOM_ice_shelf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -607,15 +607,16 @@ subroutine shelf_calc_flux(sfc_state, fluxes, Time, time_step, CS, forces)
ISS%tflux_ocn(i,j) = 0.0
endif

! haline_driving(:,:) = sfc_state%sss(i,j) - Sbdry(i,j)
! haline_driving(i,j) = sfc_state%sss(i,j) - Sbdry(i,j)

enddo ! i-loop
enddo ! j-loop

! ISS%water_flux = net liquid water into the ocean [R Z T-1 ~> kg m-2 s-1]
fluxes%iceshelf_melt(:,:) = ISS%water_flux(:,:) * CS%flux_factor

do j=js,je ; do i=is,ie
! ISS%water_flux = net liquid water into the ocean [R Z T-1 ~> kg m-2 s-1]
fluxes%iceshelf_melt(i,j) = ISS%water_flux(i,j) * CS%flux_factor

if ((sfc_state%ocean_mass(i,j) > CS%col_mass_melt_threshold) .and. &
(ISS%area_shelf_h(i,j) > 0.0) .and. (CS%isthermo)) then

Expand Down Expand Up @@ -653,11 +654,10 @@ subroutine shelf_calc_flux(sfc_state, fluxes, Time, time_step, CS, forces)
ISS%water_flux(i,j) = 0.0
fluxes%iceshelf_melt(i,j) = 0.0
endif ! area_shelf_h
enddo ; enddo ! i- and j-loops

! mass flux [R Z L2 T-1 ~> kg s-1], part of ISOMIP diags.
mass_flux(:,:) = 0.0
mass_flux(:,:) = ISS%water_flux(:,:) * ISS%area_shelf_h(:,:)
! mass flux [R Z L2 T-1 ~> kg s-1], part of ISOMIP diags.
mass_flux(i,j) = ISS%water_flux(i,j) * ISS%area_shelf_h(i,j)
enddo ; enddo ! i- and j-loops

if (CS%active_shelf_dynamics .or. CS%override_shelf_movement) then
call cpu_clock_begin(id_clock_pass)
Expand Down Expand Up @@ -690,7 +690,7 @@ subroutine shelf_calc_flux(sfc_state, fluxes, Time, time_step, CS, forces)
! advect the ice shelf, and advance the front. Calving will be in here somewhere as well..
! when we decide on how to do it
call update_ice_shelf(CS%dCS, ISS, G, US, US%s_to_T*time_step, Time, &
sfc_state%ocean_mass(:,:), coupled_GL)
sfc_state%ocean_mass, coupled_GL)

endif

Expand Down Expand Up @@ -1735,7 +1735,9 @@ subroutine update_shelf_mass(G, US, CS, ISS, Time)

call time_interp_external(CS%id_read_mass, Time, ISS%mass_shelf)
! This should only be done if time_interp_external did an update.
ISS%mass_shelf(:,:) = US%kg_m3_to_R*US%m_to_Z * ISS%mass_shelf(:,:) ! Rescale after time_interp
do j=js,je ; do i=is,ie
ISS%mass_shelf(i,j) = US%kg_m3_to_R*US%m_to_Z * ISS%mass_shelf(i,j) ! Rescale after time_interp
enddo ; enddo

do j=js,je ; do i=is,ie
ISS%area_shelf_h(i,j) = 0.0
Expand Down
Loading

0 comments on commit 3e7766a

Please sign in to comment.