source: palm/tags/release-5.0/SOURCE/eqn_state_seawater.f90 @ 4106

Last change on this file since 4106 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

  • Property svn:keywords set to Id
File size: 13.3 KB
Line 
1!> @file eqn_state_seawater.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: eqn_state_seawater.f90 2696 2017-12-14 17:12:51Z gronemeier $
27! Bugfix, do not mask topography here, since density becomes zero, leading to
28! division by zero in production_e
29!
30! 2233 2017-05-30 18:08:54Z suehring
31!
32! 2232 2017-05-30 17:47:52Z suehring
33! Adjustments to new topography and surface concept
34!
35! 2031 2016-10-21 15:11:58Z knoop
36! renamed variable rho to rho_ocean
37!
38! 2000 2016-08-20 18:09:15Z knoop
39! Forced header and separation lines into 80 columns
40!
41! 1873 2016-04-18 14:50:06Z maronga
42! Module renamed (removed _mod)
43!
44!
45! 1850 2016-04-08 13:29:27Z maronga
46! Module renamed
47!
48!
49! 1682 2015-10-07 23:56:08Z knoop
50! Code annotations made doxygen readable
51!
52! 1353 2014-04-08 15:21:23Z heinze
53! REAL constants provided with KIND-attribute
54!
55! 1320 2014-03-20 08:40:49Z raasch
56! ONLY-attribute added to USE-statements,
57! kind-parameters added to all INTEGER and REAL declaration statements,
58! kinds are defined in new module kinds,
59! revision history before 2012 removed,
60! comment fields (!:) to be used for variable explanations added to
61! all variable declaration statements
62!
63! 1036 2012-10-22 13:43:42Z raasch
64! code put under GPL (PALM 3.9)
65!
66! 97 2007-06-21 08:23:15Z raasch
67! Initial revision
68!
69!
70! Description:
71! ------------
72!> Equation of state for seawater as a function of potential temperature,
73!> salinity, and pressure.
74!> For coefficients see Jackett et al., 2006: J. Atm. Ocean Tech.
75!> eqn_state_seawater calculates the potential density referred at hyp(0).
76!> eqn_state_seawater_func calculates density.
77!------------------------------------------------------------------------------!
78 MODULE eqn_state_seawater_mod
79 
80   
81    USE kinds
82
83    IMPLICIT NONE
84
85    PRIVATE
86    PUBLIC eqn_state_seawater, eqn_state_seawater_func
87
88    REAL(wp), DIMENSION(12), PARAMETER ::  nom =                               &
89                          (/ 9.9984085444849347D2,   7.3471625860981584D0,     &
90                            -5.3211231792841769D-2,  3.6492439109814549D-4,    &
91                             2.5880571023991390D0,  -6.7168282786692354D-3,    &
92                             1.9203202055760151D-3,  1.1798263740430364D-2,    &
93                             9.8920219266399117D-8,  4.6996642771754730D-6,    &
94                            -2.5862187075154352D-8, -3.2921414007960662D-12 /)
95                          !<
96
97    REAL(wp), DIMENSION(13), PARAMETER ::  den =                               &
98                          (/ 1.0D0,                  7.2815210113327091D-3,    &
99                            -4.4787265461983921D-5,  3.3851002965802430D-7,    &
100                             1.3651202389758572D-10, 1.7632126669040377D-3,    &
101                            -8.8066583251206474D-6, -1.8832689434804897D-10,   &
102                             5.7463776745432097D-6,  1.4716275472242334D-9,    &
103                             6.7103246285651894D-6, -2.4461698007024582D-17,   &
104                            -9.1534417604289062D-18 /)
105                          !<
106
107    INTERFACE eqn_state_seawater
108       MODULE PROCEDURE eqn_state_seawater
109       MODULE PROCEDURE eqn_state_seawater_ij
110    END INTERFACE eqn_state_seawater
111 
112    INTERFACE eqn_state_seawater_func
113       MODULE PROCEDURE eqn_state_seawater_func
114    END INTERFACE eqn_state_seawater_func
115 
116 CONTAINS
117
118
119!------------------------------------------------------------------------------!
120! Description:
121! ------------
122!> Call for all grid points
123!------------------------------------------------------------------------------!
124    SUBROUTINE eqn_state_seawater
125
126       USE arrays_3d,                                                          &
127           ONLY:  hyp, prho, pt_p, rho_ocean, sa_p
128       USE indices,                                                            &
129           ONLY:  nxl, nxr, nyn, nys, nzb, nzt
130
131       USE surface_mod,                                                        &
132          ONLY :  bc_h
133
134       IMPLICIT NONE
135
136       INTEGER(iwp) ::  i       !< running index x direction
137       INTEGER(iwp) ::  j       !< running index y direction
138       INTEGER(iwp) ::  k       !< running index z direction
139       INTEGER(iwp) ::  l       !< running index of surface type, south- or north-facing wall
140       INTEGER(iwp) ::  m       !< running index surface elements
141       INTEGER(iwp) ::  surf_e  !< End index of surface elements at (j,i)-gridpoint
142       INTEGER(iwp) ::  surf_s  !< Start index of surface elements at (j,i)-gridpoint
143
144       REAL(wp) ::  pden   !<
145       REAL(wp) ::  pnom   !<
146       REAL(wp) ::  p1     !<
147       REAL(wp) ::  p2     !<
148       REAL(wp) ::  p3     !<
149       REAL(wp) ::  pt1    !<
150       REAL(wp) ::  pt2    !<
151       REAL(wp) ::  pt3    !<
152       REAL(wp) ::  pt4    !<
153       REAL(wp) ::  sa1    !<
154       REAL(wp) ::  sa15   !<
155       REAL(wp) ::  sa2    !<
156       
157                       
158
159       DO  i = nxl, nxr
160          DO  j = nys, nyn
161             DO  k = nzb+1, nzt
162!
163!--             Pressure is needed in dbar
164                p1 = hyp(k) * 1E-4_wp
165                p2 = p1 * p1
166                p3 = p2 * p1
167
168!
169!--             Temperature needed in degree Celsius
170                pt1 = pt_p(k,j,i) - 273.15_wp
171                pt2 = pt1 * pt1
172                pt3 = pt1 * pt2
173                pt4 = pt2 * pt2
174
175                sa1  = sa_p(k,j,i)
176                sa15 = sa1 * SQRT( sa1 )
177                sa2  = sa1 * sa1
178
179                pnom = nom(1)           + nom(2)*pt1     + nom(3)*pt2     +    &
180                       nom(4)*pt3       + nom(5)*sa1     + nom(6)*sa1*pt1 +    &
181                       nom(7)*sa2
182
183                pden = den(1)           + den(2)*pt1     + den(3)*pt2     +    &
184                       den(4)*pt3       + den(5)*pt4     + den(6)*sa1     +    &
185                       den(7)*sa1*pt1   + den(8)*sa1*pt3 + den(9)*sa15    +    &
186                       den(10)*sa15*pt2
187!
188!--             Potential density (without pressure terms)
189                prho(k,j,i) = pnom / pden 
190
191                pnom = pnom +             nom(8)*p1      + nom(9)*p1*pt2  +    &
192                       nom(10)*p1*sa1   + nom(11)*p2     + nom(12)*p2*pt2
193
194                pden = pden +             den(11)*p1     + den(12)*p2*pt3 +    &
195                       den(13)*p3*pt1
196
197!
198!--             In-situ density
199                rho_ocean(k,j,i) = pnom / pden 
200
201             ENDDO
202!
203!--          Neumann conditions are assumed at top boundary
204             prho(nzt+1,j,i)      = prho(nzt,j,i)
205             rho_ocean(nzt+1,j,i) = rho_ocean(nzt,j,i)
206
207          ENDDO
208       ENDDO
209!
210!--    Neumann conditions at up/downward-facing surfaces
211       !$OMP PARALLEL DO PRIVATE( i, j, k )
212       DO  m = 1, bc_h(0)%ns
213          i = bc_h(0)%i(m)           
214          j = bc_h(0)%j(m)
215          k = bc_h(0)%k(m)
216          prho(k-1,j,i)      = prho(k,j,i)
217          rho_ocean(k-1,j,i) = rho_ocean(k,j,i)
218       ENDDO
219!
220!--    Downward facing surfaces
221       !$OMP PARALLEL DO PRIVATE( i, j, k )
222       DO  m = 1, bc_h(1)%ns
223          i = bc_h(1)%i(m)           
224          j = bc_h(1)%j(m)
225          k = bc_h(1)%k(m)
226          prho(k+1,j,i)      = prho(k,j,i)
227          rho_ocean(k+1,j,i) = rho_ocean(k,j,i)
228       ENDDO
229
230    END SUBROUTINE eqn_state_seawater
231
232
233!------------------------------------------------------------------------------!
234! Description:
235! ------------
236!> Call for grid point i,j
237!------------------------------------------------------------------------------!
238    SUBROUTINE eqn_state_seawater_ij( i, j )
239
240       USE arrays_3d,                                                          &
241           ONLY:  hyp, prho, pt_p, rho_ocean, sa_p
242           
243       USE indices,                                                            &
244           ONLY:  nzb, nzt
245
246       USE surface_mod,                                                        &
247          ONLY :  bc_h
248
249       IMPLICIT NONE
250
251       INTEGER(iwp) ::  i       !< running index x direction
252       INTEGER(iwp) ::  j       !< running index y direction
253       INTEGER(iwp) ::  k       !< running index z direction
254       INTEGER(iwp) ::  l       !< running index of surface type, south- or north-facing wall
255       INTEGER(iwp) ::  m       !< running index surface elements
256       INTEGER(iwp) ::  surf_e  !< End index of surface elements at (j,i)-gridpoint
257       INTEGER(iwp) ::  surf_s  !< Start index of surface elements at (j,i)-gridpoint
258
259       REAL(wp) ::  pden   !<
260       REAL(wp) ::  pnom   !<
261       REAL(wp) ::  p1     !<
262       REAL(wp) ::  p2     !<
263       REAL(wp) ::  p3     !<
264       REAL(wp) ::  pt1    !<
265       REAL(wp) ::  pt2    !<
266       REAL(wp) ::  pt3    !<
267       REAL(wp) ::  pt4    !<
268       REAL(wp) ::  sa1    !<
269       REAL(wp) ::  sa15   !<
270       REAL(wp) ::  sa2    !<
271
272       DO  k = nzb+1, nzt
273!
274!--       Pressure is needed in dbar
275          p1 = hyp(k) * 1E-4_wp
276          p2 = p1 * p1
277          p3 = p2 * p1
278
279!
280!--       Temperature needed in degree Celsius
281          pt1 = pt_p(k,j,i) - 273.15_wp
282          pt2 = pt1 * pt1
283          pt3 = pt1 * pt2
284          pt4 = pt2 * pt2
285
286          sa1  = sa_p(k,j,i)
287          sa15 = sa1 * SQRT( sa1 )
288          sa2  = sa1 * sa1
289
290          pnom = nom(1)           + nom(2)*pt1     + nom(3)*pt2     +          &
291                 nom(4)*pt3       + nom(5)*sa1     + nom(6)*sa1*pt1 +          &
292                 nom(7)*sa2
293
294          pden = den(1)           + den(2)*pt1     + den(3)*pt2     +          &
295                 den(4)*pt3       + den(5)*pt4     + den(6)*sa1     +          &
296                 den(7)*sa1*pt1   + den(8)*sa1*pt3 + den(9)*sa15    +          &
297                 den(10)*sa15*pt2
298!
299!--       Potential density (without pressure terms)
300          prho(k,j,i) = pnom / pden 
301
302          pnom = pnom +             nom(8)*p1      + nom(9)*p1*pt2  +          &
303                 nom(10)*p1*sa1   + nom(11)*p2     + nom(12)*p2*pt2
304          pden = pden +             den(11)*p1     + den(12)*p2*pt3 +          &
305                 den(13)*p3*pt1
306
307!
308!--       In-situ density
309          rho_ocean(k,j,i) = pnom / pden 
310
311
312       ENDDO
313!
314!--    Neumann conditions at up/downward-facing walls
315       surf_s = bc_h(0)%start_index(j,i)   
316       surf_e = bc_h(0)%end_index(j,i)   
317       DO  m = surf_s, surf_e
318          k                  = bc_h(0)%k(m)
319          prho(k-1,j,i)      = prho(k,j,i)
320          rho_ocean(k-1,j,i) = rho_ocean(k,j,i)
321       ENDDO
322!
323!--    Downward facing surfaces
324       surf_s = bc_h(1)%start_index(j,i)   
325       surf_e = bc_h(1)%end_index(j,i)   
326       DO  m = surf_s, surf_e
327          k                  = bc_h(1)%k(m)
328          prho(k+1,j,i)      = prho(k,j,i)
329          rho_ocean(k+1,j,i) = rho_ocean(k,j,i)
330       ENDDO
331!
332!--    Neumann condition are assumed at top boundary
333       prho(nzt+1,j,i)      = prho(nzt,j,i)
334       rho_ocean(nzt+1,j,i) = rho_ocean(nzt,j,i)
335
336    END SUBROUTINE eqn_state_seawater_ij
337
338
339!------------------------------------------------------------------------------!
340! Description:
341! ------------
342!> Equation of state as a function
343!------------------------------------------------------------------------------!
344    REAL(wp) FUNCTION eqn_state_seawater_func( p, pt, sa )
345
346       IMPLICIT NONE
347
348       REAL(wp) ::  p      !<
349       REAL(wp) ::  p1     !<
350       REAL(wp) ::  p2     !<
351       REAL(wp) ::  p3     !<
352       REAL(wp) ::  pt     !<
353       REAL(wp) ::  pt1    !<
354       REAL(wp) ::  pt2    !<
355       REAL(wp) ::  pt3    !<
356       REAL(wp) ::  pt4    !<
357       REAL(wp) ::  sa     !<
358       REAL(wp) ::  sa15   !<
359       REAL(wp) ::  sa2    !<
360
361!
362!--    Pressure is needed in dbar
363       p1 = p  * 1E-4_wp
364       p2 = p1 * p1
365       p3 = p2 * p1
366
367!
368!--    Temperature needed in degree Celsius
369       pt1 = pt - 273.15_wp
370       pt2 = pt1 * pt1
371       pt3 = pt1 * pt2
372       pt4 = pt2 * pt2
373
374       sa15 = sa * SQRT( sa )
375       sa2  = sa * sa
376
377
378       eqn_state_seawater_func =                                               &
379         ( nom(1)        + nom(2)*pt1       + nom(3)*pt2    + nom(4)*pt3     + &
380           nom(5)*sa     + nom(6)*sa*pt1    + nom(7)*sa2    + nom(8)*p1      + &
381           nom(9)*p1*pt2 + nom(10)*p1*sa    + nom(11)*p2    + nom(12)*p2*pt2   &
382         ) /                                                                   &
383         ( den(1)        + den(2)*pt1       + den(3)*pt2    + den(4)*pt3     + &
384           den(5)*pt4    + den(6)*sa        + den(7)*sa*pt1 + den(8)*sa*pt3  + &
385           den(9)*sa15   + den(10)*sa15*pt2 + den(11)*p1    + den(12)*p2*pt3 + &
386           den(13)*p3*pt1                                                      &
387         )
388
389
390    END FUNCTION eqn_state_seawater_func
391
392 END MODULE eqn_state_seawater_mod
Note: See TracBrowser for help on using the repository browser.