Skip to content

Commit

Permalink
Rename MOM_cvmix_tidal module as MOM_tidal_mixing (for now)
Browse files Browse the repository at this point in the history
  • Loading branch information
alperaltuntas committed Mar 16, 2018
1 parent c2dea88 commit 95406ff
Show file tree
Hide file tree
Showing 2 changed files with 38 additions and 33 deletions.
19 changes: 9 additions & 10 deletions src/parameterizations/vertical/MOM_diabatic_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@ module MOM_diabatic_driver
use MOM_diffConvection, only : diffConvection_calculate, diffConvection_end
use MOM_domains, only : pass_var, To_West, To_South, To_All, Omit_Corners
use MOM_domains, only : create_group_pass, do_group_pass, group_pass_type
use MOM_cvmix_tidal, only : cvmix_tidal_init, cvmix_tidal_cs
use MOM_cvmix_tidal, only : calculate_cvmix_tidal, cvmix_tidal_end
use MOM_tidal_mixing, only : tidal_mixing_init, tidal_mixing_cs
use MOM_tidal_mixing, only : calculate_cvmix_tidal, tidal_mixing_end
use MOM_energetic_PBL, only : energetic_PBL, energetic_PBL_init
use MOM_energetic_PBL, only : energetic_PBL_end, energetic_PBL_CS
use MOM_energetic_PBL, only : energetic_PBL_get_MLD
Expand Down Expand Up @@ -92,8 +92,7 @@ module MOM_diabatic_driver
!! shear-driven diapycnal diffusivity.
logical :: use_cvmix_shear !< If true, use the CVMix module to find the
!! shear-driven diapycnal diffusivity.
logical :: use_cvmix_tidal !< If true, use the CVMix module to compute the
!! tidal mixing diffusivity.
logical :: use_tidal_mixing !< If true, activate tidal mixing diffusivity.
logical :: use_sponge !< If true, sponges may be applied anywhere in the
!! domain. The exact location and properties of
!! those sponges are set by calls to
Expand Down Expand Up @@ -224,7 +223,7 @@ module MOM_diabatic_driver
type(optics_type), pointer :: optics => NULL()
type(diag_to_Z_CS), pointer :: diag_to_Z_CSp => NULL()
type(KPP_CS), pointer :: KPP_CSp => NULL()
type(cvmix_tidal_cs), pointer :: cvmix_tidal_csp => NULL()
type(tidal_mixing_cs), pointer :: tidal_mixing_csp => NULL()
type(diffConvection_CS), pointer :: Conv_CSp => NULL()
type(diapyc_energy_req_CS), pointer :: diapyc_en_rec_CSp => NULL()

Expand Down Expand Up @@ -671,8 +670,8 @@ subroutine diabatic(u, v, h, tv, Hml, fluxes, visc, ADp, CDp, dt, Time_end, G, G

endif ! endif for KPP

! Add diffusivity due to tidal mixing (computed via CVMix)
if (CS%use_cvmix_tidal) then
! Add diffusivity due to tidal mixing
if (CS%use_tidal_mixing) then
continue !TODO
end if

Expand Down Expand Up @@ -2333,8 +2332,8 @@ subroutine diabatic_driver_init(Time, G, GV, param_file, useALEalgorithm, diag,
allocate(CS%frazil_heat_diag(isd:ied,jsd:jed,nz) ) ; CS%frazil_heat_diag(:,:,:) = 0.
endif

! CS%use_cvmix_tidal is set to True if CVMix tidal mixing will be used, otherwise false.
CS%use_cvmix_tidal = cvmix_tidal_init(Time, G, GV, param_file, diag, CS%cvmix_tidal_csp)
! CS%use_tidal_mixing is set to True tidal mixing will be activated, otherwise false.
CS%use_tidal_mixing = tidal_mixing_init(Time, G, GV, param_file, diag, CS%tidal_mixing_CSp)

! CS%useConvection is set to True IF convection will be used, otherwise False.
! CS%Conv_CSp is allocated by diffConvection_init()
Expand Down Expand Up @@ -2427,7 +2426,7 @@ subroutine diabatic_driver_end(CS)
call KPP_end(CS%KPP_CSp)
endif

if (CS%use_cvmix_tidal) call cvmix_tidal_end(CS%cvmix_tidal_csp)
if (CS%use_tidal_mixing) call tidal_mixing_end(CS%tidal_mixing_CSp)

if (CS%useConvection) call diffConvection_end(CS%Conv_CSp)
if (CS%use_energetic_PBL) &
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!> Interface to CVMix tidal mixing scheme.
module MOM_cvmix_tidal
!> Interface to vertical tidal mixing schemes including CVMix tidal mixing.
module MOM_tidal_mixing

! This file is part of MOM6. See LICENSE.md for the license.

Expand All @@ -19,12 +19,12 @@ module MOM_cvmix_tidal

#include <MOM_memory.h>

public cvmix_tidal_init
public tidal_mixing_init
public calculate_cvmix_tidal
public cvmix_tidal_end
public tidal_mixing_end

!> Control structure including parameters for CVMix tidal mixing.
type, public :: cvmix_tidal_cs
!> Control structure including parameters for tidal mixing.
type, public :: tidal_mixing_cs
logical :: debug = .true.

! Parameters
Expand All @@ -34,29 +34,28 @@ module MOM_cvmix_tidal
real :: vert_decay_scale !< zeta in the Simmons paper (to compute the vertical deposition function). [m]
real :: tidal_max_coef !< maximum allowable tidel diffusivity. [m^2/s]

end type cvmix_tidal_cs
end type tidal_mixing_cs

character(len=40) :: mdl = "MOM_cvmix_tidal" !< This module's name.
character(len=40) :: mdl = "MOM_tidal_mixing" !< This module's name.

contains

!> Initialize the cvmix tidal mixing routine.
logical function cvmix_tidal_init(Time, G, GV, param_file, diag, CS)
logical function tidal_mixing_init(Time, G, GV, param_file, diag, CS)

type(time_type), intent(in) :: Time !< The current time.
type(ocean_grid_type), intent(in) :: G !< Grid structure.
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure.
type(param_file_type), intent(in) :: param_file !< Run-time parameter file handle
type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure.
type(cvmix_tidal_cs), pointer :: CS !< This module's control structure.
type(tidal_mixing_cs), pointer :: CS !< This module's control structure.

! Local variables

! This include declares and sets the variable "version".
#include "version_variable.h"

if (associated(CS)) then
call MOM_error(WARNING, "cvmix_tidal_init called when control structure "// &
call MOM_error(WARNING, "tidal_mixing_init called when control structure "// &
"is already associated.")
return
endif
Expand All @@ -66,11 +65,18 @@ logical function cvmix_tidal_init(Time, G, GV, param_file, diag, CS)

! Read parameters
call log_version(param_file, mdl, version, &
"Parameterization of tidal mixing via CVMix")
call get_param(param_file, mdl, "USE_CVMIX_TIDAL", cvmix_tidal_init, &
"Vertical Tidal Mixing Parameterization")
!call get_param(param_file, mdl, "INT_TIDE_DISSIPATION", CS%Int_tide_dissipation, &
! "If true, use an internal tidal dissipation scheme to \n"//&
! "drive diapycnal mixing, along the lines of St. Laurent \n"//&
! "et al. (2002) and Simmons et al. (2004).", default=.false.)
if (.not. tidal_mixing_init) return


call get_param(param_file, mdl, "USE_CVMIX_TIDAL", tidal_mixing_init, &
"If true, turns on tidal mixing scheme via CVMix", &
default=.false.)
call openParameterBlock(param_file,'CVMIX_TIDAL')
!call openParameterBlock(param_file,'CVMIX_TIDAL')
call get_param(param_file, mdl, "LOCAL_MIXING_FRAC", CS%local_mixing_frac, &
"Fraction of wave energy dissipated locally.", &
units="nondim", default=0.33)
Expand All @@ -85,11 +91,10 @@ logical function cvmix_tidal_init(Time, G, GV, param_file, diag, CS)
call get_param(param_file, mdl, "TIDAL_MAX_COEF", CS%tidal_max_coef, &
"largest acceptable value for tidal diffusivity", &
units="m^2/s", default=100e-4) ! the default is 50e-4 in CVMIX, 100e-4 in POP.
call closeParameterBlock(param_file)
!call closeParameterBlock(param_file)

if (.not. cvmix_tidal_init) return

if (CS%debug) print *, __FILE__, __LINE__, cvmix_tidal_init
if (CS%debug) print *, __FILE__, __LINE__, tidal_mixing_init

! Set up CVMix
call cvmix_init_tidal(mix_scheme = 'Simmons', &
Expand All @@ -99,10 +104,11 @@ logical function cvmix_tidal_init(Time, G, GV, param_file, diag, CS)
local_mixing_frac = cs%local_mixing_frac, &
depth_cutoff = 0.0)

! TODO: read in energy



end function cvmix_tidal_init
end function tidal_mixing_init


!> ....
Expand All @@ -112,12 +118,12 @@ end subroutine calculate_cvmix_tidal


!> Clear pointers and deallocate memory
subroutine cvmix_tidal_end(CS)
type(cvmix_tidal_cs), pointer :: CS ! This module's control structure
subroutine tidal_mixing_end(CS)
type(tidal_mixing_cs), pointer :: CS ! This module's control structure

!TODO deallocate all the dynamically allocated members here ...
deallocate(CS)
end subroutine cvmix_tidal_end
end subroutine tidal_mixing_end


end module MOM_cvmix_tidal
end module MOM_tidal_mixing

0 comments on commit 95406ff

Please sign in to comment.