MOM6
MOM_diffConvection.F90
Go to the documentation of this file.
2 
3 use mom_diag_mediator, only : time_type, diag_ctrl, safe_alloc_ptr, post_data
5 use mom_error_handler, only : mom_error, mom_mesg, fatal, warning, is_root_pe
11 
12 implicit none ; private
13 
14 #include "MOM_memory.h"
15 
17 
18 ! Control structure for containing KPP parameters/data
19 type, public :: diffconvection_cs ; private
20 
21  ! Parameters
22  real :: kd_convection ! The value of diffusivity to add at statically unstable interfaces (m2/s)
23  logical :: debug ! If true, turn on debugging
24  logical :: passivemode ! If true, make the motions but go nowhere
25 
26  ! Daignostic handles and pointers
27  type(diag_ctrl), pointer :: diag => null()
28  integer :: id_n2 = -1, id_kd_conv = -1
29 
30  ! Diagnostics arrays
31  real, allocatable, dimension(:,:,:) :: n2 ! Brunt-Vaisala frequency (1/s2)
32  real, allocatable, dimension(:,:,:) :: kd_conv ! Diffusivity added by convection (m2/s)
33 
34 end type diffconvection_cs
35 
36 ! Module data used for debugging only
37 logical, parameter :: verbose = .false.
38 
39 contains
40 
41 logical function diffconvection_init(paramFile, G, diag, Time, CS)
42 !< Initialize the CVmix KPP module and set up diagnostics
43 !! Returns True if module is to be used, otherwise returns False.
44 
45 ! Arguments
46  type(param_file_type), intent(in) :: paramFile !< File parser
47  type(ocean_grid_type), intent(in) :: G !< Ocean grid
48  type(diag_ctrl), target, intent(in) :: diag !< Diagnostics
49  type(time_type), intent(in) :: Time !< Time
50  type(diffconvection_cs), pointer :: CS !< Control structure
51 ! Local variables
52 #include "version_variable.h"
53  character(len=40) :: mdl = 'MOM_diffConvection' ! This module's name.
54 
55  if (associated(cs)) call mom_error(fatal, 'MOM_diffConvection, diffConvection_init: '// &
56  'Control structure has already been initialized')
57  allocate(cs)
58 
59 ! Read parameters
60  call log_version(paramfile, mdl, version, &
61  'This module implements enhanced diffusivity as a\n' // &
62  'function of static stability, N^2.')
63  call get_param(paramfile, mdl, "USE_CONVECTION", diffconvection_init, &
64  "If true, turns on the diffusive convection scheme that\n"// &
65  "increases diapycnal diffusivities at statically unstable\n"// &
66  "interfaces. Relevant parameters are contained in the\n"// &
67  "CONVECTION% parameter block.", &
68  default=.false.)
69 
70  call openparameterblock(paramfile,'CONVECTION')
71  call get_param(paramfile, mdl, 'PASSIVE', cs%passiveMode, &
72  'If True, puts KPP into a passive-diagnostic mode.', &
73  default=.false.)
74  call get_param(paramfile, mdl, 'KD_CONV', cs%Kd_convection, &
75  'DIffusivity used in statically unstable regions of column.', &
76  units='m2/s', default=1.00)
77  call closeparameterblock(paramfile)
78  call get_param(paramfile, mdl, 'DEBUG', cs%debug, default=.false., do_not_log=.true.)
79 
80 ! Forego remainder of initialization if not using this scheme
81  if (.not. diffconvection_init) return
82 
83 ! Register diagnostics
84  cs%diag => diag
85  cs%id_N2 = register_diag_field('ocean_model', 'Conv_N2', diag%axesTi, time, &
86  'Square of Brunt-Vaisala frequency used by diffConvection module', '1/s2')
87  if (cs%id_N2 > 0) allocate( cs%N2( szi_(g), szj_(g), szk_(g)+1 ) )
88  cs%id_Kd_conv = register_diag_field('ocean_model', 'Conv_Kd', diag%axesTi, time, &
89  'Additional diffusivity added by diffConvection module', 'm2/s')
90  if (cs%id_Kd_conv > 0) allocate( cs%Kd_conv( szi_(g), szj_(g), szk_(g)+1 ) )
91 
92  if (cs%id_N2 > 0) cs%N2(:,:,:) = 0.
93  if (cs%id_Kd_conv > 0) cs%Kd_conv(:,:,:) = 0.
94 
95 end function diffconvection_init
96 
97 
98 subroutine diffconvection_calculate(CS, G, GV, h, Temp, Salt, EOS, Kd_int)
99 !< Calculates diffusivity and non-local transport for KPP parameterization
100 
101 ! Arguments
102  type(diffconvection_cs), pointer :: CS !< Control structure
103  type(ocean_grid_type), intent(in) :: G !< Ocean grid
104  type(verticalgrid_type), intent(in) :: GV !< Ocean vertical grid
105  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer/level thicknesses (units of H)
106  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Temp !< Pot. temperature (degrees C)
107  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Salt !< Salinity (ppt)
108  type(eos_type), pointer :: EOS !< Equation of state
109  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), intent(inout) :: Kd_int !< (in) Vertical diffusivity on interfaces (m2/s)
110  !! (out) Modified vertical diffusivity (m2/s)
111 ! Local variables
112  integer :: i, j, k
113  real, dimension( G%ke+1 ) :: N2_1d ! Brunt-Vaisala frequency squared, at interfaces (1/s2)
114  real, dimension( G%ke+1 ) :: Kd_1d ! Vertical diffusivity at interfaces (m2/s)
115  real :: GoRho, pRef, rhoK, rhoKm1
116 
117  gorho = gv%g_Earth / gv%Rho0
118 
119  n2_1d( 1 ) = 0.
120  n2_1d( g%ke+1 ) = 0.
121  kd_1d( 1 ) = 0.
122  kd_1d( g%ke+1 ) = 0.
123  do j=g%jsc,g%jec ; do i=g%isc,g%iec
124  ! This k-loop calculates external quantities independent of any iterations
125  ! Start at bottom of top level
126  pref = 0. ! Ignore atmospheric pressure
127  do k = 2, g%ke
128  ! Pressure at interface K is incremented by mass of level above
129  pref = pref + gv%g_Earth * gv%Rho0 * h(i,j,k-1) * gv%H_to_m ! Boussinesq approximation!!!! ?????
130  ! Compute Brunt-Vaisala frequency (static stability) on interfaces
131  call calculate_density(temp(i,j,k), salt(i,j,k), pref, rhok, eos)
132  call calculate_density(temp(i,j,k-1), salt(i,j,k-1), pref, rhokm1, eos)
133  n2_1d(k) = gorho * (rhok - rhokm1) / &
134  (0.5*(h(i,j,k-1) + h(i,j,k)) + gv%H_subroundoff) ! Can be negative
135  kd_1d(k) = 0.
136  if (n2_1d(k) < 0.) kd_1d(k) = cs%Kd_convection
137  enddo ! k
138 
139  if (.not. cs%passiveMode) kd_int(i,j,:) = kd_int(i,j,:) + kd_1d(:)
140 
141  if (cs%id_N2 > 0) cs%N2(i,j,:) = n2_1d(:)
142  if (cs%id_Kd_conv > 0) cs%Kd_conv(i,j,:) = kd_1d(:)
143 
144  enddo ; enddo ! j
145 
146  if (cs%id_N2 > 0) call post_data(cs%id_N2, cs%N2, cs%diag)
147  if (cs%id_Kd_conv > 0) call post_data(cs%id_Kd_conv, cs%Kd_conv, cs%diag)
148 
149 end subroutine diffconvection_calculate
150 
151 
152 subroutine diffconvection_end(CS)
153 ! Clear pointers, dealocate memory
154  type(diffconvection_cs), pointer :: CS ! Control structure
155 
156  if (cs%id_N2 > 0) deallocate(cs%N2, cs%diag)
157  if (cs%id_Kd_conv > 0) deallocate(cs%Kd_conv, cs%diag)
158  deallocate(cs)
159 end subroutine diffconvection_end
160 
161 end module mom_diffconvection
logical function, public ispointincell(G, i, j, x, y)
Returns true if the coordinates (x,y) are within the h-cell (i,j)
Definition: MOM_grid.F90:406
logical function, public diffconvection_init(paramFile, G, diag, Time, CS)
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
subroutine, public diffconvection_calculate(CS, G, GV, h, Temp, Salt, EOS, Kd_int)
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:45
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public diffconvection_end(CS)
logical function, public query_averaging_enabled(diag_cs, time_int, time_end)
subroutine, public closeparameterblock(CS)
subroutine, public openparameterblock(CS, blockName, desc)
logical function, public is_root_pe()
subroutine, public mom_mesg(message, verb, all_print)
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
logical, parameter verbose
integer function, public register_diag_field(module_name, field_name, axes, init_time, long_name, units, missing_value, range, mask_variant, standard_name, verbose, do_not_log, err_msg, interp_method, tile_count, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name, cell_methods, x_cell_method, y_cell_method, v_cell_method, conversion, v_extensive)
Returns the "diag_mediator" handle for a group (native, CMOR, z-coord, ...) of diagnostics derived fr...
subroutine, public mom_error(level, message, all_print)
A control structure for the equation of state.
Definition: MOM_EOS.F90:55