FV3 Bundle
gsw_ipv_vs_fnsquared_ratio.f90
Go to the documentation of this file.
1 !==========================================================================
2 pure subroutine gsw_ipv_vs_fnsquared_ratio (sa, ct, p, p_ref, &
3  ipv_vs_fnsquared_ratio, p_mid)
4 !==========================================================================
5 !
6 ! Calculates the ratio of the vertical gradient of potential density to
7 ! the vertical gradient of locally-referenced potential density. This
8 ! ratio is also the ratio of the planetary Isopycnal Potential Vorticity
9 ! (IPV) to f times N^2, hence the name for this variable,
10 ! IPV_vs_fNsquared_ratio (see Eqn. (3.20.5) of IOC et al. (2010)).
11 ! The reference sea pressure, p_ref, of the potential density surface must
12 ! have a constant value.
13 !
14 ! IPV_vs_fNsquared_ratio is evaluated at the mid pressure between the
15 ! individual data points in the vertical.
16 
17 ! sa : Absolute Salinity (a profile (length nz)) [g/kg]
18 ! ct : Conservative Temperature (a profile (length nz)) [deg C]
19 ! p : sea pressure (a profile (length nz)) [dbar]
20 ! p_ref : reference sea pressure of the potential density surface
21 ! ( i.e. absolute reference pressure - 10.1325 dbar ) [dbar]
22 ! IPV_vs_fNsquared_ratio
23 ! : The ratio of the vertical gradient of potential density
24 ! referenced to p_ref, to the vertical gradient of locally-
25 ! referenced potential density. It is ouput on the same
26 ! vertical (M-1)xN grid as p_mid.
27 ! IPV_vs_fNsquared_ratio is dimensionless. [ unitless ]
28 ! p_mid : Mid pressure between p grid (length nz-1) [dbar]
29 !--------------------------------------------------------------------------
30 
32 
34 
35 use gsw_mod_kinds
36 
37 implicit none
38 
39 real (r8), intent(in) :: sa(:), ct(:), p(:), p_ref
40 real (r8), intent(out) :: ipv_vs_fnsquared_ratio(:), p_mid(:)
41 
42 integer :: nz, i
43 real (r8), dimension(:), allocatable :: dsa, sa_mid, dct, ct_mid, vp_ref
44 real (r8), dimension(:), allocatable :: alpha_mid, beta_mid, alpha_pref
45 real (r8), dimension(:), allocatable :: beta_pref, numerator, denominator
46 
47 character (*), parameter :: func_name = "gsw_ipv_vs_fnsquared_ratio"
48 
49 nz = size(sa)
50 if (size(ipv_vs_fnsquared_ratio).lt.nz-1 .or. size(p_mid).lt.nz-1) then
51  ipv_vs_fnsquared_ratio = gsw_error_code(1,func_name)
52  p_mid = ipv_vs_fnsquared_ratio(1)
53  return
54 end if
55 
56 allocate (dsa(nz-1), sa_mid(nz-1), dct(nz-1), ct_mid(nz-1))
57 allocate (vp_ref(nz-1), alpha_mid(nz-1), beta_mid(nz-1), alpha_pref(nz-1))
58 allocate (beta_pref(nz-1), numerator(nz-1), denominator(nz-1))
59 
60 forall (i = 1: nz-1)
61  dsa(i) = sa(i) - sa(i+1)
62  dct(i) = ct(i) - ct(i+1)
63  sa_mid(i) = 0.5_r8*(sa(i) + sa(i+1))
64  ct_mid(i) = 0.5_r8*(ct(i) + ct(i+1))
65  p_mid(i) = 0.5_r8*(p(i) + p(i+1))
66 end forall
67 
68 vp_ref = p_ref
69 alpha_mid = gsw_alpha(sa_mid,ct_mid,p_mid(1:nz-1))
70 beta_mid = gsw_beta(sa_mid,ct_mid,p_mid(1:nz-1))
71 alpha_pref = gsw_alpha(sa_mid,ct_mid,vp_ref)
72 beta_pref = gsw_beta(sa_mid,ct_mid,vp_ref)
73 
74 numerator = dct*alpha_pref - dsa*beta_pref
75 denominator = dct*alpha_mid - dsa*beta_mid
76 
77 where (denominator /= 0.0_r8)
78  ipv_vs_fnsquared_ratio = numerator/denominator
79 elsewhere
80  ipv_vs_fnsquared_ratio = gsw_error_code(2,func_name)
81 end where
82 
83 deallocate (dsa, sa_mid, dct, ct_mid)
84 deallocate (vp_ref, alpha_mid, beta_mid, alpha_pref)
85 deallocate (beta_pref, numerator, denominator)
86 
87 return
88 end subroutine
89 
90 !--------------------------------------------------------------------------
pure subroutine gsw_ipv_vs_fnsquared_ratio(sa, ct, p, p_ref, ipv_vs_fnsquared_ratio, p_mid)
elemental real(r8) function, public gsw_error_code(err_num, func_name, error_code)