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

Last change on this file since 3253 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

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