Skip to content

Commit 431cb7d

Browse files
vanroekelmark-petersen
authored andcommitted
Changes to CVMix forcing and interface
This changes the amount of shortwave radiation in the boundary layer which decreases vertical resolution sensitivity. It also removes the shear instability driven mixing scheme from operating in the boundary layer to reduce grid scale noise.
1 parent 769791f commit 431cb7d

6 files changed

+37
-68
lines changed

src/core_ocean/Registry.xml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -650,10 +650,6 @@
650650
description="Integer value defining the water type used in Jerlov short wave absorption."
651651
possible_values="Integer values between 1 and 5"
652652
/>
653-
<nml_option name="config_surface_buoyancy_depth" type="real" default_value="1" units="m"
654-
description="Depth over which to apply penetrating SW to sfcBuoyancyFlux"
655-
possible_values="Real Values greater than zero less than bottomDepth"
656-
/>
657653
</nml_record>
658654
<nml_record name="tidal_forcing" mode="init;forward">
659655
<nml_option name="config_use_tidal_forcing" type="logical" default_value=".false." units="unitless"

src/core_ocean/shared/mpas_ocn_tendency.F

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -889,8 +889,9 @@ subroutine ocn_tend_tracer(tendPool, statePool, forcingPool, diagnosticsPool, me
889889
!$omp end parallel
890890
endif
891891

892-
call ocn_tracer_short_wave_absorption_tend(meshPool, swForcingPool, forcingPool, indexTemperature, &
893-
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tracerGroupTend, err)
892+
call ocn_tracer_short_wave_absorption_tend(meshPool, diagnosticsPool, swForcingPool, forcingPool, &
893+
indexTemperature, layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, &
894+
tracerGroupTend, err)
894895

895896
if (config_compute_active_tracer_budgets) then
896897
!$omp parallel

src/core_ocean/shared/mpas_ocn_tracer_short_wave_absorption.F

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -64,8 +64,9 @@ module ocn_tracer_short_wave_absorption
6464
!
6565
!-----------------------------------------------------------------------
6666

67-
subroutine ocn_tracer_short_wave_absorption_tend(meshPool, swForcingPool, forcingPool, index_temperature, & !{{{
68-
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)
67+
subroutine ocn_tracer_short_wave_absorption_tend(meshPool, diagnosticsPool, swForcingPool, forcingPool, & !{{{
68+
index_temperature, layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, &
69+
tend, err)
6970

7071
!-----------------------------------------------------------------
7172
!
@@ -74,7 +75,7 @@ subroutine ocn_tracer_short_wave_absorption_tend(meshPool, swForcingPool, forcin
7475
!-----------------------------------------------------------------
7576

7677
type (mpas_pool_type), intent(in) :: &
77-
meshPool, swForcingPool, forcingPool !< Input: mesh information
78+
meshPool, swForcingPool, diagnosticsPool, forcingPool !< Input: mesh information
7879

7980
real (kind=RKIND), dimension(:), intent(in) :: &
8081
penetrativeTemperatureFlux !< Input: short wave heat flux
@@ -115,11 +116,11 @@ subroutine ocn_tracer_short_wave_absorption_tend(meshPool, swForcingPool, forcin
115116

116117
err = 0
117118
if(useJerlov) then
118-
call ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, index_temperature, layerThickness, &
119-
penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)
119+
call ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, diagnosticsPool, forcingPool, index_temperature, &
120+
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)
120121
else
121-
call ocn_tracer_short_wave_absorption_variable_tend(meshPool,swForcingPool, forcingPool, index_temperature, &
122-
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL,tend,err)
122+
call ocn_tracer_short_wave_absorption_variable_tend(meshPool, diagnosticsPool, swForcingPool, forcingPool, &
123+
index_temperature, layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL,tend,err)
123124
endif
124125

125126
call mpas_timer_stop("short wave")

src/core_ocean/shared/mpas_ocn_tracer_short_wave_absorption_jerlov.F

Lines changed: 10 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -75,8 +75,8 @@ module ocn_tracer_short_wave_absorption_jerlov
7575
!
7676
!-----------------------------------------------------------------------
7777

78-
subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, index_temperature, layerThickness, &
79-
penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)!{{{
78+
subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, diagnosticsPool, forcingPool, index_temperature, &!{{{
79+
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)
8080

8181
!-----------------------------------------------------------------
8282
!
@@ -85,7 +85,7 @@ subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, i
8585
!-----------------------------------------------------------------
8686

8787
type (mpas_pool_type), intent(in) :: &
88-
meshPool, forcingPool !< Input: mesh information
88+
meshPool, forcingPool, diagnosticsPool !< Input: mesh information
8989

9090
real (kind=RKIND), dimension(:), intent(in) :: &
9191
penetrativeTemperatureFlux !< Input: penetrative temperature flux through the surface
@@ -120,21 +120,22 @@ subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, i
120120
!
121121
!-----------------------------------------------------------------
122122

123-
integer :: iCell, k, depLev, nCells
123+
integer :: iCell, k, nCells
124124
integer, pointer :: nVertLevels
125125
integer, dimension(:), pointer :: nCellsArray
126126

127127
integer, dimension(:), pointer :: maxLevelCell
128128

129-
real (kind=RKIND) :: depth
130-
real (kind=RKIND), dimension(:), pointer :: refBottomDepth
129+
real (kind=RKIND) :: depth, weightOSBL
130+
real (kind=RKIND), dimension(:), pointer :: boundaryLayerDepth, refBottomDepth
131131
real (kind=RKIND), dimension(:), allocatable :: weights
132132

133133
err = 0
134134

135135
call mpas_pool_get_dimension(meshPool, 'nCellsArray', nCellsArray)
136136
call mpas_pool_get_dimension(meshPool, 'nVertLevels', nVertLevels)
137137

138+
call mpas_pool_get_array(diagnosticsPool, 'boundaryLayerDepth', boundaryLayerDepth)
138139
call mpas_pool_get_array(meshPool, 'maxLevelCell', maxLevelCell)
139140
call mpas_pool_get_array(meshPool, 'refBottomDepth', refBottomDepth)
140141

@@ -146,7 +147,7 @@ subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, i
146147

147148
#ifndef CPRPGI
148149
!$omp parallel
149-
!$omp do schedule(runtime) private(depth, k, depLev) &
150+
!$omp do schedule(runtime) private(weightOSBL, depth, k) &
150151
!$omp firstprivate(weights)
151152
#endif
152153
do iCell = 1, nCells
@@ -159,18 +160,8 @@ subroutine ocn_tracer_short_wave_absorption_jerlov_tend(meshPool, forcingPool, i
159160
* (weights(k) - weights(k+1))
160161
end do
161162

162-
depth = 0.0_RKIND
163-
do k=1,maxLevelCell(iCell)
164-
depth = depth + layerThickness(k,iCell)
165-
if(depth > abs(config_surface_buoyancy_depth)) exit
166-
enddo
167-
168-
if(k == maxLevelCell(iCell) .or. k == 1) then
169-
depLev=2
170-
else
171-
depLev=k
172-
endif
173-
penetrativeTemperatureFluxOBL(iCell)=penetrativeTemperatureFlux(iCell)*weights(depLev)
163+
call ocn_get_jerlov_fraction(boundaryLayerDepth(iCell), weightOSBL)
164+
penetrativeTemperatureFluxOBL(iCell)=penetrativeTemperatureFlux(iCell)*weightOSBL
174165

175166
end do
176167
#ifndef CPRPGI

src/core_ocean/shared/mpas_ocn_tracer_short_wave_absorption_variable.F

Lines changed: 12 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,9 @@ module ocn_tracer_short_wave_absorption_variable
7171
!
7272
!-----------------------------------------------------------------------
7373

74-
subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPool, forcingPool, index_temperature, & !{{{
75-
layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, err)
74+
subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, diagnosticsPool, swForcingPool, forcingPool, &!{{{
75+
index_temperature, layerThickness, penetrativeTemperatureFlux, penetrativeTemperatureFluxOBL, tend, &
76+
err)
7677

7778
!-----------------------------------------------------------------
7879
!
@@ -84,7 +85,8 @@ subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPoo
8485
type (mpas_pool_type), intent(in) :: &
8586
meshPool, & !< Input: mesh information
8687
swForcingPool, & !< Input: chlorophyll, cloud, zenith data
87-
forcingPool
88+
forcingPool, &
89+
diagnosticsPool
8890

8991
real (kind=RKIND), dimension(:), intent(in) :: &
9092
penetrativeTemperatureFlux !< Input: penetrative temperature flux through the surface
@@ -119,14 +121,14 @@ subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPoo
119121
!
120122
!-----------------------------------------------------------------
121123

122-
integer :: iCell, k, depLev, nCells
124+
integer :: iCell, k, nCells
123125
integer, pointer :: nVertLevels
124126
integer, dimension(:), pointer :: nCellsArray
125127

126128
integer, dimension(:), pointer :: maxLevelCell
127129

128-
real (kind=RKIND) :: depth
129-
real (kind=RKIND), dimension(:), pointer :: refBottomDepth
130+
real (kind=RKIND) :: weightOSBL, depth
131+
real (kind=RKIND), dimension(:), pointer :: boundaryLayerDepth, refBottomDepth
130132
real (kind=RKIND), dimension(:), allocatable :: weights
131133
real (kind=RKIND), dimension(:), pointer :: chlorophyllA, zenithAngle, clearSkyRadiation
132134
real (kind=RKIND), dimension(4) :: Avals, Kvals
@@ -139,6 +141,7 @@ subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPoo
139141

140142
call mpas_pool_get_array(meshPool, 'maxLevelCell', maxLevelCell)
141143
call mpas_pool_get_array(meshPool, 'refBottomDepth', refBottomDepth)
144+
call mpas_pool_get_array(diagnosticsPool, 'boundaryLayerDepth', boundaryLayerDepth)
142145

143146
allocate(weights(nVertLevels+1))
144147
weights = 0.0_RKIND
@@ -154,7 +157,7 @@ subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPoo
154157
nCells = nCellsArray( 3 )
155158

156159
!$omp parallel
157-
!$omp do schedule(runtime) private(depth, cloudRatio, k, depLev, Avals, Kvals, weights)
160+
!$omp do schedule(runtime) private(depth, cloudRatio, k, weightOSBL, Avals, Kvals, weights)
158161
do iCell = 1, nCells
159162
depth = 0.0_RKIND
160163
cloudRatio = min(1.0_RKIND, 1.0_RKIND - penetrativeTemperatureFlux(iCell)/(hflux_factor*(1.0E-15_RKIND + &
@@ -171,18 +174,8 @@ subroutine ocn_tracer_short_wave_absorption_variable_tend(meshPool, swForcingPoo
171174
* (weights(k) - weights(k+1) )
172175
end do
173176

174-
depth = 0.0_RKIND
175-
do k=1,maxLevelCell(iCell)
176-
depth = depth + layerThickness(k,iCell)
177-
if(depth > abs(config_surface_buoyancy_depth)) exit
178-
enddo
179-
180-
if(k == maxLevelCell(iCell) .or. k == 1) then
181-
depLev=2
182-
else
183-
depLev=k
184-
endif
185-
penetrativeTemperatureFluxOBL(iCell)=penetrativeTemperatureFlux(iCell)*weights(depLev)
177+
call ocn_get_variable_sw_fraction(boundaryLayerDepth(iCell), weightOSBL, Avals, Kvals)
178+
penetrativeTemperatureFluxOBL(iCell)=penetrativeTemperatureFlux(iCell)*weightOSBL
186179

187180
end do
188181
!$omp end do

src/core_ocean/shared/mpas_ocn_vmix_cvmix.F

Lines changed: 4 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -674,23 +674,10 @@ subroutine ocn_vmix_coefs_cvmix_build(meshPool, statePool, forcingPool, diagnost
674674
! intent out of BoundaryLayerDepth is boundary layer depth measured in meters and vertical index
675675
indexBoundaryLayerDepth(iCell) = cvmix_variables % kOBL_depth
676676

677-
678-
679-
if(config_cvmix_kpp_matching .eq. 'SimpleShapes') then
680-
do k = 1, int(indexBoundaryLayerDepth(iCell))
681-
vertViscTopOfCell(k,iCell) = vertViscTopOfCell(k,iCell) + cvmix_variables % Mdiff_iface(k)
682-
vertDiffTopOfCell(k,iCell) = vertDiffTopOfCell(k,iCell) + cvmix_variables % Tdiff_iface(k)
683-
end do
684-
do k = int(indexBoundaryLayerDepth(iCell))+1, maxLevelCell(iCell)+1
685-
vertViscTopOfCell(k,iCell) = cvmix_variables % Mdiff_iface(k)
686-
vertDiffTopOfCell(k,iCell) = cvmix_variables % Tdiff_iface(k)
687-
enddo
688-
else
689-
do k = 1, maxLevelCell(iCell) + 1
690-
vertViscTopOfCell(k, iCell) = cvmix_variables % Mdiff_iface(k)
691-
vertDiffTopOfCell(k, iCell) = cvmix_variables % Tdiff_iface(k)
692-
end do
693-
endif
677+
do k = 1, maxLevelCell(iCell) + 1
678+
vertViscTopOfCell(k, iCell) = cvmix_variables % Mdiff_iface(k)
679+
vertDiffTopOfCell(k, iCell) = cvmix_variables % Tdiff_iface(k)
680+
end do
694681

695682
! store non-local flux terms
696683
! these flux terms must be multiplied by the surfaceTracerFlux field

0 commit comments

Comments
 (0)