FV3 Bundle
gsw_pot_to_insitu.f90
Go to the documentation of this file.
2 !===============================================================================
3 !
4 ! MODULE:
5 ! gsw_pot_to_insitu
6 !
7 ! PURPOSE:
8 ! This module provides additional subroutines needed to compute the in situ
9 ! temperature from a numerical model's potential temperature (ÂșC) and practical
10 ! salinity (psu). It utilizes the TEOS GSW Fortran package, version 3.03,
11 ! available at http://www.teos-10.org
12 !
13 !
14 !-------------------------------------------------------------------------------
15 ! Author: Steve Penny
16 ! Institution: University of Maryland, College Park; NWS/NOAA/NCEP
17 ! Contact: Steve.Penny@noaa.gov
18 !===============================================================================
19 
20 use kinds
21 
22 IMPLICIT NONE
23 
24 PUBLIC :: t_from_pt, p_from_z ! Computing in situ from potential temperature
25 PUBLIC :: sa_from_sp, pt_from_t ! Computing potential temperature from in situ
26 
27 PRIVATE
28 
29 !INTEGER, PARAMETER :: r14 = selected_real_kind(14,30)
30 
31 CONTAINS
32 
33 !===============================================================================
34 FUNCTION t_from_pt(pt_in,sp_in,p_in,lon_in,lat_in)
35 !===============================================================================
36  !USE common, ONLY: r_size
37 
38  use gsw_mod_toolbox, only : gsw_ct_from_pt
40  use gsw_mod_toolbox, only : gsw_t_from_ct
41  use gsw_mod_kinds
42 
43  !USE gsw_oceanographic_toolbox, ONLY: gsw_sa_from_sp, gsw_ct_from_pt, gsw_t_from_ct !, r14
44  !STEVE: The toolbox is not coded as a module, so this will not work.
45  ! I'll leave it unaltered as a list of functions in order to facilitate forward compatibility.
46 
47  IMPLICIT NONE
48  real(kind_real) :: t_from_pt
49  real(kind_real), INTENT(IN) :: pt_in, sp_in, p_in, lon_in, lat_in
50  real(kind_real) :: pt, sp, p, lon, lat
51  real(kind_real) :: sa, ct, t
52 
53  pt = pt_in
54  sp = sp_in
55  p = p_in
56  lon = lon_in
57  lat = lat_in
58 
59 ! Compute in situ temperature from potential temperature by computing
60 ! the conservative temperature from potential temperature then computing
61 ! the in situ temperature from the conservative temperature.
62 ! sa : Absolute Salinity [g/kg]
63 ! sp : Practical Salinity [unitless]
64 ! ct : Conservative Temperature [deg C]
65 ! pt : potential temperature with [deg C]
66 ! reference pressure of 0 dbar
67 ! c : conductivity [mS/cm]
68 ! t : in-situ temperature [ITS-90] [deg C]
69 ! p : sea pressure [dbar]
70 ! z : depth [m]
71 
72  ! Compute the absolute salinity from the practical salinity
73  sa = gsw_sa_from_sp(sp,p,lon,lat)
74 
75  ! Compute the conservative temperature
76  ct = gsw_ct_from_pt(sa,pt)
77 
78  ! Compute the in situ temperature
79  t_from_pt = gsw_t_from_ct(sa,ct,p)
80 
81 END FUNCTION t_from_pt
82 
83 !===============================================================================
84 PURE FUNCTION p_from_z(dpth,xlat)
85 !===============================================================================
86 ! pressure from depth from saunder's formula with eos80.
87 ! reference: saunders,peter m., practical conversion of pressure
88 ! to depth., j.p.o. , april 1981.
89 ! r millard
90 ! march 9, 1983
91 ! check value: p_from_z=7500.004 dbars;for lat=30 deg., depth=7321.45 meters
92 ! http://sam.ucsd.edu/sio210/propseawater/ppsw_fortran/ppsw.f
93  IMPLICIT NONE
94  real(kind_real) :: p_from_z
95  real(kind_real), INTENT(IN) :: dpth
96  real(kind_real), INTENT(IN) :: xlat
97  real(kind_real), PARAMETER :: pi=3.141592654
98  real(kind_real) :: plat, d, c1
99 
100  plat=abs(xlat*pi/180.)
101  d=sin(plat)
102  c1=5.92e-3+d**2*5.25e-3
103  p_from_z=((1-c1)-sqrt(((1-c1)**2)-(8.84e-6*dpth)))/4.42e-6
104 
105 END FUNCTION p_from_z
106 
107 !===============================================================================
108 FUNCTION sa_from_sp(sp,p,long,lat)
109 !===============================================================================
110 
111 ! Calculates Absolute Salinity, SA, from Practical Salinity, SP
112 !
113 ! sp : Practical Salinity [unitless]
114 ! p : sea pressure [dbar]
115 ! long : longitude [DEG E]
116 ! lat : latitude [DEG N]
117 !
118 ! gsw_sa_from_sp : Absolute Salinity [g/kg]
119 
120 IMPLICIT NONE
121 real(kind_real) :: sa_from_sp
122 real(kind_real), INTENT(IN) :: sp, long, lat, p
123 real(kind_real) :: gsw_sa_from_sp
124 
125 sa_from_sp = gsw_sa_from_sp(sp,p,long,lat)
126 
127 END FUNCTION sa_from_sp
128 
129 !===============================================================================
130 FUNCTION pt_from_t(sa,t,p,p_ref)
131 !===============================================================================
132 
133 ! Calculates potential temperature of seawater from in-situ temperature
134 !
135 ! sa : Absolute Salinity [g/kg]
136 ! t : in-situ temperature [deg C]
137 ! p : sea pressure [dbar]
138 ! p_ref : reference sea pressure [dbar]
139 !
140 ! gsw_pt_from_t : potential temperature [deg C]
141 
142 IMPLICIT NONE
143 real(kind_real) :: pt_from_t
144 real(kind_real), INTENT(IN) :: sa, t, p, p_ref
145 real(kind_real) :: gsw_pt_from_t
146 
147 pt_from_t = gsw_pt_from_t(sa,t,p,p_ref)
148 
149 END FUNCTION pt_from_t
150 
151 END MODULE gsw_pot_to_insitu
elemental real(r8) function gsw_sa_from_sp(sp, p, long, lat)
integer, parameter, public long
Definition: Type_Kinds.f90:76
real(kind_real) function, public pt_from_t(sa, t, p, p_ref)
real(kind_real) function, public t_from_pt(pt_in, sp_in, p_in, lon_in, lat_in)
elemental real(r8) function gsw_pt_from_t(sa, t, p, p_ref)
real(kind_real) function, public sa_from_sp(sp, p, long, lat)
pure real(kind_real) function, public p_from_z(dpth, xlat)
real(fp), parameter, public pi