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

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

revised renaming of modules

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