source: palm/trunk/SOURCE/eqn_state_seawater.f90 @ 1320

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 10.2 KB
Line 
1 MODULE eqn_state_seawater_mod
2
3!------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! old module precision_kind is removed,
26! revision history before 2012 removed,
27! comment fields (!:) to be used for variable explanations added to
28! all variable declaration statements
29!
30! Former revisions:
31! -----------------
32! $Id: eqn_state_seawater.f90 1320 2014-03-20 08:40:49Z raasch $
33!
34! 1036 2012-10-22 13:43:42Z raasch
35! code put under GPL (PALM 3.9)
36!
37! 97 2007-06-21 08:23:15Z raasch
38! Initial revision
39!
40!
41! Description:
42! ------------
43! Equation of state for seawater as a function of potential temperature,
44! salinity, and pressure.
45! For coefficients see Jackett et al., 2006: J. Atm. Ocean Tech.
46! eqn_state_seawater calculates the potential density referred at hyp(0).
47! eqn_state_seawater_func calculates density.
48!------------------------------------------------------------------------------!
49   
50    USE kinds
51
52    IMPLICIT NONE
53
54    PRIVATE
55    PUBLIC eqn_state_seawater, eqn_state_seawater_func
56
57    REAL(wp), DIMENSION(12), PARAMETER ::  nom =                               &
58                          (/ 9.9984085444849347D2,   7.3471625860981584D0,     &
59                            -5.3211231792841769D-2,  3.6492439109814549D-4,    &
60                             2.5880571023991390D0,  -6.7168282786692354D-3,    &
61                             1.9203202055760151D-3,  1.1798263740430364D-2,    &
62                             9.8920219266399117D-8,  4.6996642771754730D-6,    &
63                            -2.5862187075154352D-8, -3.2921414007960662D-12 /)
64                          !:
65
66    REAL(wp), DIMENSION(13), PARAMETER ::  den =                               &
67                          (/ 1.0D0,                  7.2815210113327091D-3,    &
68                            -4.4787265461983921D-5,  3.3851002965802430D-7,    &
69                             1.3651202389758572D-10, 1.7632126669040377D-3,    &
70                            -8.8066583251206474D-6, -1.8832689434804897D-10,   &
71                             5.7463776745432097D-6,  1.4716275472242334D-9,    &
72                             6.7103246285651894D-6, -2.4461698007024582D-17,   &
73                            -9.1534417604289062D-18 /)
74                          !:
75
76    INTERFACE eqn_state_seawater
77       MODULE PROCEDURE eqn_state_seawater
78       MODULE PROCEDURE eqn_state_seawater_ij
79    END INTERFACE eqn_state_seawater
80 
81    INTERFACE eqn_state_seawater_func
82       MODULE PROCEDURE eqn_state_seawater_func
83    END INTERFACE eqn_state_seawater_func
84 
85 CONTAINS
86
87
88!------------------------------------------------------------------------------!
89! Call for all grid points
90!------------------------------------------------------------------------------!
91    SUBROUTINE eqn_state_seawater
92
93       USE arrays_3d,                                                          &
94           ONLY:  hyp, prho, pt_p, rho, sa_p
95       USE indices,                                                            &
96           ONLY:  nxl, nxr, nyn, nys, nzb_s_inner, nzt
97
98       IMPLICIT NONE
99
100       INTEGER(iwp) ::  i  !:
101       INTEGER(iwp) ::  j  !:
102       INTEGER(iwp) ::  k  !:
103
104       REAL(wp) ::  pden  !:
105       REAL(wp) ::  pnom  !:
106       REAL(wp) ::  p1    !:
107       REAL(wp) ::  p2    !:
108       REAL(wp) ::  p3    !:
109       REAL(wp) ::  pt1   !:
110       REAL(wp) ::  pt2   !:
111       REAL(wp) ::  pt3   !:
112       REAL(wp) ::  pt4   !:
113       REAL(wp) ::  sa1   !:
114       REAL(wp) ::  sa15  !:
115       REAL(wp) ::  sa2   !:
116       
117                       
118
119       DO  i = nxl, nxr
120          DO  j = nys, nyn
121             DO  k = nzb_s_inner(j,i)+1, nzt
122!
123!--             Pressure is needed in dbar
124                p1 = hyp(k) * 1E-4
125                p2 = p1 * p1
126                p3 = p2 * p1
127
128!
129!--             Temperature needed in degree Celsius
130                pt1 = pt_p(k,j,i) - 273.15
131                pt2 = pt1 * pt1
132                pt3 = pt1 * pt2
133                pt4 = pt2 * pt2
134
135                sa1  = sa_p(k,j,i)
136                sa15 = sa1 * SQRT( sa1 )
137                sa2  = sa1 * sa1
138
139                pnom = nom(1)           + nom(2)*pt1     + nom(3)*pt2     +    &
140                       nom(4)*pt3       + nom(5)*sa1     + nom(6)*sa1*pt1 +    &
141                       nom(7)*sa2
142
143                pden = den(1)           + den(2)*pt1     + den(3)*pt2     +    &
144                       den(4)*pt3       + den(5)*pt4     + den(6)*sa1     +    &
145                       den(7)*sa1*pt1   + den(8)*sa1*pt3 + den(9)*sa15    +    &
146                       den(10)*sa15*pt2
147
148!
149!--             Potential density (without pressure terms)
150                prho(k,j,i) = pnom / pden
151
152                pnom = pnom +             nom(8)*p1      + nom(9)*p1*pt2  +    &
153                       nom(10)*p1*sa1   + nom(11)*p2     + nom(12)*p2*pt2
154
155                pden = pden +             den(11)*p1     + den(12)*p2*pt3 +    &
156                       den(13)*p3*pt1
157
158!
159!--             In-situ density
160                rho(k,j,i) = pnom / pden
161
162             ENDDO
163!
164!--          Neumann conditions are assumed at bottom and top boundary
165             prho(nzt+1,j,i)            = prho(nzt,j,i)
166             prho(nzb_s_inner(j,i),j,i) = prho(nzb_s_inner(j,i)+1,j,i)
167             rho(nzt+1,j,i)             = rho(nzt,j,i)
168             rho(nzb_s_inner(j,i),j,i)  = rho(nzb_s_inner(j,i)+1,j,i)
169
170          ENDDO
171       ENDDO
172
173    END SUBROUTINE eqn_state_seawater
174
175
176!------------------------------------------------------------------------------!
177! Call for grid point i,j
178!------------------------------------------------------------------------------!
179    SUBROUTINE eqn_state_seawater_ij( i, j )
180
181       USE arrays_3d,                                                          &
182           ONLY:  hyp, prho, pt_p, rho, sa_p
183           
184       USE indices,                                                            &
185           ONLY:  nzb_s_inner, nzt
186
187       IMPLICIT NONE
188
189       INTEGER(iwp) ::  i, j, k
190
191       REAL(wp)     ::  pden, pnom, p1, p2, p3, pt1, pt2, pt3, pt4, sa1, sa15, &
192                        sa2
193
194       DO  k = nzb_s_inner(j,i)+1, nzt
195!
196!--       Pressure is needed in dbar
197          p1 = hyp(k) * 1E-4
198          p2 = p1 * p1
199          p3 = p2 * p1
200
201!
202!--       Temperature needed in degree Celsius
203          pt1 = pt_p(k,j,i) - 273.15
204          pt2 = pt1 * pt1
205          pt3 = pt1 * pt2
206          pt4 = pt2 * pt2
207
208          sa1  = sa_p(k,j,i)
209          sa15 = sa1 * SQRT( sa1 )
210          sa2  = sa1 * sa1
211
212          pnom = nom(1)           + nom(2)*pt1     + nom(3)*pt2     +          &
213                 nom(4)*pt3       + nom(5)*sa1     + nom(6)*sa1*pt1 +          &
214                 nom(7)*sa2
215
216          pden = den(1)           + den(2)*pt1     + den(3)*pt2     +          &
217                 den(4)*pt3       + den(5)*pt4     + den(6)*sa1     +          &
218                 den(7)*sa1*pt1   + den(8)*sa1*pt3 + den(9)*sa15    +          &
219                 den(10)*sa15*pt2
220
221!
222!--       Potential density (without pressure terms)
223          prho(k,j,i) = pnom / pden
224
225          pnom = pnom +             nom(8)*p1      + nom(9)*p1*pt2  +          &
226                 nom(10)*p1*sa1   + nom(11)*p2     + nom(12)*p2*pt2
227          pden = pden +             den(11)*p1     + den(12)*p2*pt3 +          &
228                 den(13)*p3*pt1
229
230!
231!--       In-situ density
232          rho(k,j,i) = pnom / pden
233
234
235       ENDDO
236
237!
238!--    Neumann conditions are assumed at bottom and top boundary
239       prho(nzt+1,j,i)            = prho(nzt,j,i)
240       prho(nzb_s_inner(j,i),j,i) = prho(nzb_s_inner(j,i)+1,j,i)
241       rho(nzt+1,j,i)             = rho(nzt,j,i)
242       rho(nzb_s_inner(j,i),j,i)  = rho(nzb_s_inner(j,i)+1,j,i)
243
244    END SUBROUTINE eqn_state_seawater_ij
245
246
247!------------------------------------------------------------------------------!
248! Equation of state as a function
249!------------------------------------------------------------------------------!
250    REAL(wp) FUNCTION eqn_state_seawater_func( p, pt, sa )
251
252       IMPLICIT NONE
253
254       REAL(wp) ::  p      !:
255       REAL(wp) ::  p1     !:
256       REAL(wp) ::  p2     !:
257       REAL(wp) ::  p3     !:
258       REAL(wp) ::  pt     !:
259       REAL(wp) ::  pt1    !:
260       REAL(wp) ::  pt2    !:
261       REAL(wp) ::  pt3    !:
262       REAL(wp) ::  pt4    !:
263       REAL(wp) ::  sa     !:
264       REAL(wp) ::  sa15   !:
265       REAL(wp) ::  sa2    !:
266
267!
268!--    Pressure is needed in dbar
269       p1 = p  * 1E-4
270       p2 = p1 * p1
271       p3 = p2 * p1
272
273!
274!--    Temperature needed in degree Celsius
275       pt1 = pt - 273.15
276       pt2 = pt1 * pt1
277       pt3 = pt1 * pt2
278       pt4 = pt2 * pt2
279
280       sa15 = sa * SQRT( sa )
281       sa2  = sa * sa
282
283
284       eqn_state_seawater_func =                                               &
285         ( nom(1)        + nom(2)*pt1       + nom(3)*pt2    + nom(4)*pt3     + &
286           nom(5)*sa     + nom(6)*sa*pt1    + nom(7)*sa2    + nom(8)*p1      + &
287           nom(9)*p1*pt2 + nom(10)*p1*sa    + nom(11)*p2    + nom(12)*p2*pt2   &
288         ) /                                                                   &
289         ( den(1)        + den(2)*pt1       + den(3)*pt2    + den(4)*pt3     + &
290           den(5)*pt4    + den(6)*sa        + den(7)*sa*pt1 + den(8)*sa*pt3  + &
291           den(9)*sa15   + den(10)*sa15*pt2 + den(11)*p1    + den(12)*p2*pt3 + &
292           den(13)*p3*pt1                                                      &
293         )
294
295
296    END FUNCTION eqn_state_seawater_func
297
298 END MODULE eqn_state_seawater_mod
Note: See TracBrowser for help on using the repository browser.