12 implicit none ;
private 14 #include "MOM_memory.h" 24 logical :: passivemode
28 integer :: id_n2 = -1, id_kd_conv = -1
31 real,
allocatable,
dimension(:,:,:) :: n2
32 real,
allocatable,
dimension(:,:,:) :: kd_conv
48 type(
diag_ctrl),
target,
intent(in) :: diag
49 type(time_type),
intent(in) :: Time
52 #include "version_variable.h" 53 character(len=40) :: mdl =
'MOM_diffConvection' 55 if (
associated(cs))
call mom_error(fatal,
'MOM_diffConvection, diffConvection_init: '// &
56 'Control structure has already been initialized')
61 'This module implements enhanced diffusivity as a\n' // &
62 'function of static stability, N^2.')
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.", &
71 call get_param(paramfile, mdl,
'PASSIVE', cs%passiveMode, &
72 'If True, puts KPP into a passive-diagnostic mode.', &
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)
78 call get_param(paramfile, mdl,
'DEBUG', cs%debug, default=.false., do_not_log=.true.)
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 ) )
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 ) )
92 if (cs%id_N2 > 0) cs%N2(:,:,:) = 0.
93 if (cs%id_Kd_conv > 0) cs%Kd_conv(:,:,:) = 0.
105 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
106 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Temp
107 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Salt
109 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)+1),
intent(inout) :: Kd_int
113 real,
dimension( G%ke+1 ) :: N2_1d
114 real,
dimension( G%ke+1 ) :: Kd_1d
115 real :: GoRho, pRef, rhoK, rhoKm1
117 gorho = gv%g_Earth / gv%Rho0
123 do j=g%jsc,g%jec ;
do i=g%isc,g%iec
129 pref = pref + gv%g_Earth * gv%Rho0 * h(i,j,k-1) * gv%H_to_m
133 n2_1d(k) = gorho * (rhok - rhokm1) / &
134 (0.5*(h(i,j,k-1) + h(i,j,k)) + gv%H_subroundoff)
136 if (n2_1d(k) < 0.) kd_1d(k) = cs%Kd_convection
139 if (.not. cs%passiveMode) kd_int(i,j,:) = kd_int(i,j,:) + kd_1d(:)
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(:)
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)
156 if (cs%id_N2 > 0)
deallocate(cs%N2, cs%diag)
157 if (cs%id_Kd_conv > 0)
deallocate(cs%Kd_conv, cs%diag)
logical function, public ispointincell(G, i, j, x, y)
Returns true if the coordinates (x,y) are within the h-cell (i,j)
logical function, public diffconvection_init(paramFile, G, diag, Time, CS)
Ocean grid type. See mom_grid for details.
subroutine, public diffconvection_calculate(CS, G, GV, h, Temp, Salt, EOS, Kd_int)
Calculates density of sea water from T, S and P.
Provides the ocean grid type.
subroutine, public diffconvection_end(CS)
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.
logical, parameter verbose
subroutine, public mom_error(level, message, all_print)
A control structure for the equation of state.