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

Last change on this file since 1952 was 1874, checked in by maronga, 8 years ago

last commit documented

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