MOM6
circle_obcs_initialization.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
25 use mom_get_input, only : directories
26 use mom_grid, only : ocean_grid_type
31 
32 implicit none ; private
33 
34 #include <MOM_memory.h>
35 
37 
38 contains
39 
40 !> This subroutine initializes layer thicknesses for the circle_obcs experiment.
41 subroutine circle_obcs_initialize_thickness(h, G, GV, param_file, just_read_params)
42  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
43  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
44  real, dimension(SZI_(G),SZJ_(G), SZK_(GV)), &
45  intent(out) :: h !< The thickness that is being initialized, in m.
46  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
47  !! to parse for model parameter values.
48  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
49  !! only read parameters without changing h.
50 
51  real :: e0(szk_(gv)+1) ! The resting interface heights, in m, usually !
52  ! negative because it is positive upward. !
53  real :: eta1D(szk_(gv)+1)! Interface height relative to the sea surface !
54  ! positive upward, in m. !
55  real :: diskrad, rad, xCenter, xRadius, lonC, latC
56  logical :: just_read
57 ! This include declares and sets the variable "version".
58 #include "version_variable.h"
59  character(len=40) :: mdl = "circle_obcs_initialization" ! This module's name.
60  integer :: i, j, k, is, ie, js, je, nz
61 
62  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
63 
64  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
65 
66  if (.not.just_read) &
67  call mom_mesg(" circle_obcs_initialization.F90, circle_obcs_initialize_thickness: setting thickness", 5)
68 
69  if (.not.just_read) call log_version(param_file, mdl, version, "")
70  ! Parameters read by cartesian grid initialization
71  call get_param(param_file, mdl, "DISK_RADIUS", diskrad, &
72  "The radius of the initially elevated disk in the \n"//&
73  "circle_obcs test case.", units=g%x_axis_units, &
74  fail_if_missing=.not.just_read, do_not_log=just_read)
75 
76  if (just_read) return ! All run-time parameters have been read, so return.
77 
78  do k=1,nz
79  e0(k) = -g%max_depth * real(k-1) / real(nz)
80  enddo
81 
82  ! Uniform thicknesses for base state
83  do j=js,je ; do i=is,ie !
84  eta1d(nz+1) = -1.0*g%bathyT(i,j)
85  do k=nz,1,-1
86  eta1d(k) = e0(k)
87  if (eta1d(k) < (eta1d(k+1) + gv%Angstrom_z)) then
88  eta1d(k) = eta1d(k+1) + gv%Angstrom_z
89  h(i,j,k) = gv%Angstrom_z
90  else
91  h(i,j,k) = eta1d(k) - eta1d(k+1)
92  endif
93  enddo
94  enddo ; enddo
95 
96  ! Perturb base state by circular anomaly in center
97  k=nz
98  latc = g%south_lat + 0.5*g%len_lat
99  lonc = g%west_lon + 0.5*g%len_lon
100  do j=js,je ; do i=is,ie
101  rad = sqrt((g%geoLonT(i,j)-lonc)**2+(g%geoLatT(i,j)-latc)**2)/(diskrad)
102  ! if (rad <= 6.*diskrad) h(i,j,k) = h(i,j,k)+10.0*exp( -0.5*( rad**2 ) )
103  rad = min( rad, 1. ) ! Flatten outside radius of diskrad
104  rad = rad*(2.*asin(1.)) ! Map 0-1 to 0-pi
105  if (nz==1) then
106  ! The model is barotropic
107  h(i,j,k) = h(i,j,k) + 1.0*0.5*(1.+cos(rad)) ! cosine bell
108  else
109  ! The model is baroclinic
110  do k = 1, nz
111  h(i,j,k) = h(i,j,k) - 0.5*(1.+cos(rad)) & ! cosine bell
112  * 5.0 * real( 2*k-nz )
113  enddo
114  endif
115  enddo ; enddo
116 
118 
119 !> \namespace circle_obcs_initialization
120 !!
121 !! The module configures the model for the "circle_obcs" experiment.
122 !! circle_obcs = Test of Open Boundary Conditions for an SSH anomaly.
subroutine, public circle_obcs_initialize_thickness(h, G, GV, param_file, just_read_params)
This subroutine initializes layer thicknesses for the circle_obcs experiment.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
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
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
subroutine, public calculate_density_derivs(T, S, pressure, drho_dT, drho_dS, start, npts, EOS)
Calls the appropriate subroutine to calculate density derivatives for 1-D array inputs.
Definition: MOM_EOS.F90:214
subroutine, public initialize_sponge(Iresttime, int_height, G, param_file, CS, Iresttime_i_mean, int_height_i_mean)
Definition: MOM_sponge.F90:142
subroutine, public set_up_sponge_field(sp_val, f_ptr, G, nlay, CS, sp_val_i_mean)
Definition: MOM_sponge.F90:271
Type to carry basic tracer information.
logical function, public is_root_pe()
The module configures the model for the "circle_obcs" experiment. circle_obcs = Test of Open Boundary...
subroutine, public mom_mesg(message, verb, all_print)
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public mom_error(level, message, all_print)
A control structure for the equation of state.
Definition: MOM_EOS.F90:55