MOM6
coord_zlike.F90
Go to the documentation of this file.
1 !> Regrid columns for a z-like coordinate (z-star, z-level)
2 module coord_zlike
3 
4 use mom_error_handler, only : mom_error, fatal
5 
6 implicit none ; private
7 
8 !> Control structure containing required parameters for a z-like coordinate
9 type, public :: zlike_cs
10  private
11 
12  !> Number of levels
13  integer :: nk
14 
15  !> Minimum thickness allowed for layers
16  real :: min_thickness
17 
18  !> Target coordinate resolution
19  real, allocatable, dimension(:) :: coordinateresolution
20 end type zlike_cs
21 
23 
24 contains
25 
26 !> Initialise a zlike_CS with pointers to parameters
27 subroutine init_coord_zlike(CS, nk, coordinateResolution)
28  type(zlike_cs), pointer :: CS !< Unassociated pointer to hold the control structure
29  integer, intent(in) :: nk
30  real, dimension(:), intent(in) :: coordinateResolution
31 
32  if (associated(cs)) call mom_error(fatal, "init_coord_zlike: CS already associated!")
33  allocate(cs)
34  allocate(cs%coordinateResolution(nk))
35 
36  cs%nk = nk
37  cs%coordinateResolution = coordinateresolution
38 end subroutine init_coord_zlike
39 
40 subroutine end_coord_zlike(CS)
41  type(zlike_cs), pointer :: CS
42 
43  ! nothing to do
44  if (.not. associated(cs)) return
45  deallocate(cs%coordinateResolution)
46  deallocate(cs)
47 end subroutine end_coord_zlike
48 
49 subroutine set_zlike_params(CS, min_thickness)
50  type(zlike_cs), pointer :: CS
51  real, optional, intent(in) :: min_thickness
52 
53  if (.not. associated(cs)) call mom_error(fatal, "set_zlike_params: CS not associated")
54 
55  if (present(min_thickness)) cs%min_thickness = min_thickness
56 end subroutine set_zlike_params
57 
58 !> Builds a z* coordinate with a minimum thickness
59 subroutine build_zstar_column(CS, nz, depth, total_thickness, zInterface, z_rigid_top, eta_orig)
60  type(zlike_cs), intent(in) :: CS !< Coordinate control structure
61  integer, intent(in) :: nz !< Number of levels
62  real, intent(in) :: depth !< Depth of ocean bottom (positive in m)
63  real, intent(in) :: total_thickness !< Column thickness (positive in m)
64  real, dimension(nz+1), intent(inout) :: zInterface !< Absolute positions of interfaces
65  real, optional, intent(in) :: z_rigid_top !< The height of a rigid top (negative in m)
66  real, optional, intent(in) :: eta_orig !< The actual original height of the top (m)
67  ! Local variables
68  real :: eta, stretching, dh, min_thickness, z0_top, z_star
69  integer :: k
70  logical :: new_zstar_def
71 
72  new_zstar_def = .false.
73  min_thickness = min( cs%min_thickness, total_thickness/real(nz) )
74  z0_top = 0.
75  if (present(z_rigid_top)) then
76  z0_top = z_rigid_top
77  new_zstar_def = .true.
78  endif
79 
80  ! Position of free-surface (or the rigid top, for which eta ~ z0_top)
81  eta = total_thickness - depth
82  if (present(eta_orig)) eta = eta_orig
83 
84  ! Conventional z* coordinate:
85  ! z* = (z-eta) / stretching where stretching = (H+eta)/H
86  ! z = eta + stretching * z*
87  ! The above gives z*(z=eta) = 0, z*(z=-H) = -H.
88  ! With a rigid top boundary at eta = z0_top then
89  ! z* = z0 + (z-eta) / stretching where stretching = (H+eta)/(H+z0)
90  ! z = eta + stretching * (z*-z0) * stretching
91  stretching = total_thickness / ( depth + z0_top )
92 
93  if (new_zstar_def) then
94  ! z_star is the notional z* coordinate in absence of upper/lower topography
95  z_star = 0. ! z*=0 at the free-surface
96  zinterface(1) = eta ! The actual position of the top of the column
97  do k = 2,nz
98  z_star = z_star - cs%coordinateResolution(k-1)
99  ! This ensures that z is below a rigid upper surface (ice shelf bottom)
100  zinterface(k) = min( eta + stretching * ( z_star - z0_top ), z0_top )
101  ! This ensures that the layer in inflated
102  zinterface(k) = min( zinterface(k), zinterface(k-1) - min_thickness )
103  ! This ensures that z is above or at the topography
104  zinterface(k) = max( zinterface(k), -depth + real(nz+1-k) * min_thickness )
105  enddo
106  zinterface(nz+1) = -depth
107 
108  else
109  ! Integrate down from the top for a notional new grid, ignoring topography
110  ! The starting position is offset by z0_top which, if z0_top<0, will place
111  ! interfaces above the rigid boundary.
112  zinterface(1) = eta
113  do k = 1,nz
114  dh = stretching * cs%coordinateResolution(k) ! Notional grid spacing
115  zinterface(k+1) = zinterface(k) - dh
116  enddo
117 
118  ! Integrating up from the bottom adjusting interface position to accommodate
119  ! inflating layers without disturbing the interface above
120  zinterface(nz+1) = -depth
121  do k = nz,1,-1
122  if ( zinterface(k) < (zinterface(k+1) + min_thickness) ) then
123  zinterface(k) = zinterface(k+1) + min_thickness
124  endif
125  enddo
126  endif
127 
128 end subroutine build_zstar_column
129 
130 end module coord_zlike
subroutine, public end_coord_zlike(CS)
Definition: coord_zlike.F90:41
subroutine, public set_zlike_params(CS, min_thickness)
Definition: coord_zlike.F90:50
subroutine, public init_coord_zlike(CS, nk, coordinateResolution)
Initialise a zlike_CS with pointers to parameters.
Definition: coord_zlike.F90:28
subroutine, public build_zstar_column(CS, nz, depth, total_thickness, zInterface, z_rigid_top, eta_orig)
Builds a z* coordinate with a minimum thickness.
Definition: coord_zlike.F90:60
Regrid columns for a z-like coordinate (z-star, z-level)
Definition: coord_zlike.F90:2
Control structure containing required parameters for a z-like coordinate.
Definition: coord_zlike.F90:9
subroutine, public mom_error(level, message, all_print)