New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
eosbn2.F90 in trunk/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90 @ 4624

Last change on this file since 4624 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

  • Property svn:keywords set to Id
File size: 39.1 KB
Line 
1MODULE eosbn2
2   !!==============================================================================
3   !!                       ***  MODULE  eosbn2  ***
4   !! Ocean diagnostic variable : equation of state - in situ and potential density
5   !!                                               - Brunt-Vaisala frequency
6   !!==============================================================================
7   !! History :  OPA  ! 1989-03  (O. Marti)  Original code
8   !!            6.0  ! 1994-07  (G. Madec, M. Imbard)  add bn2
9   !!            6.0  ! 1994-08  (G. Madec)  Add Jackett & McDougall eos
10   !!            7.0  ! 1996-01  (G. Madec)  statement function for e3
11   !!            8.1  ! 1997-07  (G. Madec)  density instead of volumic mass
12   !!             -   ! 1999-02  (G. Madec, N. Grima) semi-implicit pressure gradient
13   !!            8.2  ! 2001-09  (M. Ben Jelloul)  bugfix on linear eos
14   !!   NEMO     1.0  ! 2002-10  (G. Madec)  add eos_init
15   !!             -   ! 2002-11  (G. Madec, A. Bozec)  partial step, eos_insitu_2d
16   !!             -   ! 2003-08  (G. Madec)  F90, free form
17   !!            3.0  ! 2006-08  (G. Madec)  add tfreez function
18   !!            3.3  ! 2010-05  (C. Ethe, G. Madec)  merge TRC-TRA
19   !!             -   ! 2010-10  (G. Nurser, G. Madec)  add eos_alpbet used in ldfslp
20   !!----------------------------------------------------------------------
21
22   !!----------------------------------------------------------------------
23   !!   eos            : generic interface of the equation of state
24   !!   eos_insitu     : Compute the in situ density
25   !!   eos_insitu_pot : Compute the insitu and surface referenced potential
26   !!                    volumic mass
27   !!   eos_insitu_2d  : Compute the in situ density for 2d fields
28   !!   eos_bn2        : Compute the Brunt-Vaisala frequency
29   !!   eos_alpbet     : calculates the in situ thermal/haline expansion ratio
30   !!   tfreez         : Compute the surface freezing temperature
31   !!   eos_init       : set eos parameters (namelist)
32   !!----------------------------------------------------------------------
33   USE dom_oce         ! ocean space and time domain
34   USE phycst          ! physical constants
35   USE zdfddm          ! vertical physics: double diffusion
36   USE in_out_manager  ! I/O manager
37   USE lib_mpp         ! MPP library
38   USE prtctl          ! Print control
39   USE wrk_nemo        ! Memory Allocation
40   USE timing          ! Timing
41
42   IMPLICIT NONE
43   PRIVATE
44
45   !                   !! * Interface
46   INTERFACE eos
47      MODULE PROCEDURE eos_insitu, eos_insitu_pot, eos_insitu_2d
48   END INTERFACE
49   INTERFACE bn2
50      MODULE PROCEDURE eos_bn2
51   END INTERFACE
52
53   PUBLIC   eos        ! called by step, istate, tranpc and zpsgrd modules
54   PUBLIC   eos_init   ! called by istate module
55   PUBLIC   bn2        ! called by step module
56   PUBLIC   eos_alpbet ! called by ldfslp module
57   PUBLIC   tfreez     ! called by sbcice_... modules
58
59   !                                  !!* Namelist (nameos) *
60   INTEGER , PUBLIC ::   nn_eos       !: = 0/1/2 type of eq. of state and Brunt-Vaisala frequ.
61   REAL(wp), PUBLIC ::   rn_alpha     !: thermal expension coeff. (linear equation of state)
62   REAL(wp), PUBLIC ::   rn_beta      !: saline  expension coeff. (linear equation of state)
63
64   REAL(wp), PUBLIC ::   ralpbet              !: alpha / beta ratio
65
66   !! * Substitutions
67#  include "domzgr_substitute.h90"
68#  include "vectopt_loop_substitute.h90"
69   !!----------------------------------------------------------------------
70   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
71   !! $Id$
72   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
73   !!----------------------------------------------------------------------
74CONTAINS
75
76   SUBROUTINE eos_insitu( pts, prd, pdep )
77      !!----------------------------------------------------------------------
78      !!                   ***  ROUTINE eos_insitu  ***
79      !!
80      !! ** Purpose :   Compute the in situ density (ratio rho/rau0) from
81      !!       potential temperature and salinity using an equation of state
82      !!       defined through the namelist parameter nn_eos.
83      !!
84      !! ** Method  :   3 cases:
85      !!      nn_eos = 0 : Jackett and McDougall (1994) equation of state.
86      !!         the in situ density is computed directly as a function of
87      !!         potential temperature relative to the surface (the opa t
88      !!         variable), salt and pressure (assuming no pressure variation
89      !!         along geopotential surfaces, i.e. the pressure p in decibars
90      !!         is approximated by the depth in meters.
91      !!              prd(t,s,p) = ( rho(t,s,p) - rau0 ) / rau0
92      !!         with pressure                      p        decibars
93      !!              potential temperature         t        deg celsius
94      !!              salinity                      s        psu
95      !!              reference volumic mass        rau0     kg/m**3
96      !!              in situ volumic mass          rho      kg/m**3
97      !!              in situ density anomalie      prd      no units
98      !!         Check value: rho = 1060.93298 kg/m**3 for p=10000 dbar,
99      !!          t = 40 deg celcius, s=40 psu
100      !!      nn_eos = 1 : linear equation of state function of temperature only
101      !!              prd(t) = 0.0285 - rn_alpha * t
102      !!      nn_eos = 2 : linear equation of state function of temperature and
103      !!               salinity
104      !!              prd(t,s) = rn_beta * s - rn_alpha * tn - 1.
105      !!      Note that no boundary condition problem occurs in this routine
106      !!      as pts are defined over the whole domain.
107      !!
108      !! ** Action  :   compute prd , the in situ density (no units)
109      !!
110      !! References :   Jackett and McDougall, J. Atmos. Ocean. Tech., 1994
111      !!----------------------------------------------------------------------
112      !!
113      REAL(wp), DIMENSION(:,:,:,:), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celcius]
114      !                                                      ! 2 : salinity               [psu]
115      REAL(wp), DIMENSION(:,:,:)  , INTENT(  out) ::   prd   ! in situ density            [-]
116      REAL(wp), DIMENSION(:,:,:)  , INTENT(in   ) ::   pdep  ! depth                      [m]
117      !!
118      INTEGER  ::   ji, jj, jk           ! dummy loop indices
119      REAL(wp) ::   zt , zs , zh , zsr   ! local scalars
120      REAL(wp) ::   zr1, zr2, zr3, zr4   !   -      -
121      REAL(wp) ::   zrhop, ze, zbw, zb   !   -      -
122      REAL(wp) ::   zd , zc , zaw, za    !   -      -
123      REAL(wp) ::   zb1, za1, zkw, zk0   !   -      -
124      REAL(wp), POINTER, DIMENSION(:,:,:) :: zws
125      !!----------------------------------------------------------------------
126
127      !
128      IF( nn_timing == 1 ) CALL timing_start('eos')
129      !
130      CALL wrk_alloc( jpi, jpj, jpk, zws )
131      !
132      SELECT CASE( nn_eos )
133      !
134      CASE( 0 )                !==  Jackett and McDougall (1994) formulation  ==!
135!CDIR NOVERRCHK
136         zws(:,:,:) = SQRT( ABS( pts(:,:,:,jp_sal) ) )
137         !
138         DO jk = 1, jpkm1
139            DO jj = 1, jpj
140               DO ji = 1, jpi
141                  zt = pts   (ji,jj,jk,jp_tem)
142                  zs = pts   (ji,jj,jk,jp_sal)
143                  zh = pdep(ji,jj,jk)        ! depth
144                  zsr= zws   (ji,jj,jk)        ! square root salinity
145                  !
146                  ! compute volumic mass pure water at atm pressure
147                  zr1= ( ( ( ( 6.536332e-9_wp  *zt - 1.120083e-6_wp )*zt + 1.001685e-4_wp )*zt   &
148                     &        -9.095290e-3_wp )*zt + 6.793952e-2_wp )*zt +  999.842594_wp
149                  ! seawater volumic mass atm pressure
150                  zr2= ( ( ( 5.3875e-9_wp*zt-8.2467e-7_wp ) *zt+7.6438e-5_wp ) *zt        &
151                     &                      -4.0899e-3_wp ) *zt+0.824493_wp
152                  zr3= ( -1.6546e-6_wp*zt+1.0227e-4_wp )    *zt-5.72466e-3_wp
153                  zr4= 4.8314e-4_wp
154                  !
155                  ! potential volumic mass (reference to the surface)
156                  zrhop= ( zr4*zs + zr3*zsr + zr2 ) *zs + zr1
157                  !
158                  ! add the compression terms
159                  ze = ( -3.508914e-8_wp*zt-1.248266e-8_wp ) *zt-2.595994e-6_wp
160                  zbw= (  1.296821e-6_wp*zt-5.782165e-9_wp ) *zt+1.045941e-4_wp
161                  zb = zbw + ze * zs
162                  !
163                  zd = -2.042967e-2_wp
164                  zc =   (-7.267926e-5_wp*zt+2.598241e-3_wp ) *zt+0.1571896_wp
165                  zaw= ( ( 5.939910e-6_wp*zt+2.512549e-3_wp ) *zt-0.1028859_wp ) *zt - 4.721788_wp
166                  za = ( zd*zsr + zc ) *zs + zaw
167                  !
168                  zb1=   (-0.1909078_wp*zt+7.390729_wp )        *zt-55.87545_wp
169                  za1= ( ( 2.326469e-3_wp*zt+1.553190_wp)       *zt-65.00517_wp ) *zt+1044.077_wp
170                  zkw= ( ( (-1.361629e-4_wp*zt-1.852732e-2_wp ) *zt-30.41638_wp ) *zt + 2098.925_wp ) *zt+190925.6_wp
171                  zk0= ( zb1*zsr + za1 )*zs + zkw
172                  !
173                  ! masked in situ density anomaly
174                  prd(ji,jj,jk) = (  zrhop / (  1.0_wp - zh / ( zk0 - zh * ( za - zh * zb ) )  )    &
175                     &             - rau0  ) * r1_rau0 * tmask(ji,jj,jk)
176               END DO
177            END DO
178         END DO
179         !
180      CASE( 1 )                !==  Linear formulation function of temperature only  ==!
181         DO jk = 1, jpkm1
182            prd(:,:,jk) = ( 0.0285_wp - rn_alpha * pts(:,:,jk,jp_tem) ) * tmask(:,:,jk)
183         END DO
184         !
185      CASE( 2 )                !==  Linear formulation function of temperature and salinity  ==!
186         DO jk = 1, jpkm1
187            prd(:,:,jk) = ( rn_beta  * pts(:,:,jk,jp_sal) - rn_alpha * pts(:,:,jk,jp_tem) ) * tmask(:,:,jk)
188         END DO
189         !
190      END SELECT
191      !
192      IF(ln_ctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos  : ', ovlap=1, kdim=jpk )
193      !
194      CALL wrk_dealloc( jpi, jpj, jpk, zws )
195      !
196      IF( nn_timing == 1 ) CALL timing_stop('eos')
197      !
198   END SUBROUTINE eos_insitu
199
200
201   SUBROUTINE eos_insitu_pot( pts, prd, prhop, pdep )
202      !!----------------------------------------------------------------------
203      !!                  ***  ROUTINE eos_insitu_pot  ***
204      !!
205      !! ** Purpose :   Compute the in situ density (ratio rho/rau0) and the
206      !!      potential volumic mass (Kg/m3) from potential temperature and
207      !!      salinity fields using an equation of state defined through the
208      !!     namelist parameter nn_eos.
209      !!
210      !! ** Method  :
211      !!      nn_eos = 0 : Jackett and McDougall (1994) equation of state.
212      !!         the in situ density is computed directly as a function of
213      !!         potential temperature relative to the surface (the opa t
214      !!         variable), salt and pressure (assuming no pressure variation
215      !!         along geopotential surfaces, i.e. the pressure p in decibars
216      !!         is approximated by the depth in meters.
217      !!              prd(t,s,p) = ( rho(t,s,p) - rau0 ) / rau0
218      !!              rhop(t,s)  = rho(t,s,0)
219      !!         with pressure                      p        decibars
220      !!              potential temperature         t        deg celsius
221      !!              salinity                      s        psu
222      !!              reference volumic mass        rau0     kg/m**3
223      !!              in situ volumic mass          rho      kg/m**3
224      !!              in situ density anomalie      prd      no units
225      !!
226      !!         Check value: rho = 1060.93298 kg/m**3 for p=10000 dbar,
227      !!          t = 40 deg celcius, s=40 psu
228      !!
229      !!      nn_eos = 1 : linear equation of state function of temperature only
230      !!              prd(t) = ( rho(t) - rau0 ) / rau0 = 0.028 - rn_alpha * t
231      !!              rhop(t,s)  = rho(t,s)
232      !!
233      !!      nn_eos = 2 : linear equation of state function of temperature and
234      !!               salinity
235      !!              prd(t,s) = ( rho(t,s) - rau0 ) / rau0
236      !!                       = rn_beta * s - rn_alpha * tn - 1.
237      !!              rhop(t,s)  = rho(t,s)
238      !!      Note that no boundary condition problem occurs in this routine
239      !!      as (tn,sn) or (ta,sa) are defined over the whole domain.
240      !!
241      !! ** Action  : - prd  , the in situ density (no units)
242      !!              - prhop, the potential volumic mass (Kg/m3)
243      !!
244      !! References :   Jackett and McDougall, J. Atmos. Ocean. Tech., 1994
245      !!                Brown and Campana, Mon. Weather Rev., 1978
246      !!----------------------------------------------------------------------
247      !!
248      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celcius]
249      !                                                                ! 2 : salinity               [psu]
250      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(  out) ::   prd    ! in situ density            [-]
251      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(  out) ::   prhop  ! potential density (surface referenced)
252      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pdep   ! depth                      [m]
253      !
254      INTEGER  ::   ji, jj, jk   ! dummy loop indices
255      REAL(wp) ::   zt, zs, zh, zsr, zr1, zr2, zr3, zr4, zrhop, ze, zbw   ! local scalars
256      REAL(wp) ::   zb, zd, zc, zaw, za, zb1, za1, zkw, zk0               !   -      -
257      REAL(wp), POINTER, DIMENSION(:,:,:) :: zws
258      !!----------------------------------------------------------------------
259      !
260      IF( nn_timing == 1 ) CALL timing_start('eos-p')
261      !
262      CALL wrk_alloc( jpi, jpj, jpk, zws )
263      !
264      SELECT CASE ( nn_eos )
265      !
266      CASE( 0 )                !==  Jackett and McDougall (1994) formulation  ==!
267!CDIR NOVERRCHK
268         zws(:,:,:) = SQRT( ABS( pts(:,:,:,jp_sal) ) )
269         !
270         DO jk = 1, jpkm1
271            DO jj = 1, jpj
272               DO ji = 1, jpi
273                  zt = pts   (ji,jj,jk,jp_tem)
274                  zs = pts   (ji,jj,jk,jp_sal)
275                  zh = pdep(ji,jj,jk)        ! depth
276                  zsr= zws   (ji,jj,jk)        ! square root salinity
277                  !
278                  ! compute volumic mass pure water at atm pressure
279                  zr1= ( ( ( ( 6.536332e-9_wp*zt-1.120083e-6_wp )*zt+1.001685e-4_wp )*zt   &
280                     &                          -9.095290e-3_wp )*zt+6.793952e-2_wp )*zt+999.842594_wp
281                  ! seawater volumic mass atm pressure
282                  zr2= ( ( ( 5.3875e-9_wp*zt-8.2467e-7_wp ) *zt+7.6438e-5_wp ) *zt   &
283                     &                                         -4.0899e-3_wp ) *zt+0.824493_wp
284                  zr3= ( -1.6546e-6_wp*zt+1.0227e-4_wp )    *zt-5.72466e-3_wp
285                  zr4= 4.8314e-4_wp
286                  !
287                  ! potential volumic mass (reference to the surface)
288                  zrhop= ( zr4*zs + zr3*zsr + zr2 ) *zs + zr1
289                  !
290                  ! save potential volumic mass
291                  prhop(ji,jj,jk) = zrhop * tmask(ji,jj,jk)
292                  !
293                  ! add the compression terms
294                  ze = ( -3.508914e-8_wp*zt-1.248266e-8_wp ) *zt-2.595994e-6_wp
295                  zbw= (  1.296821e-6_wp*zt-5.782165e-9_wp ) *zt+1.045941e-4_wp
296                  zb = zbw + ze * zs
297                  !
298                  zd = -2.042967e-2_wp
299                  zc =   (-7.267926e-5_wp*zt+2.598241e-3_wp ) *zt+0.1571896_wp
300                  zaw= ( ( 5.939910e-6_wp*zt+2.512549e-3_wp ) *zt-0.1028859_wp ) *zt - 4.721788_wp
301                  za = ( zd*zsr + zc ) *zs + zaw
302                  !
303                  zb1=   (  -0.1909078_wp  *zt+7.390729_wp    ) *zt-55.87545_wp
304                  za1= ( (   2.326469e-3_wp*zt+1.553190_wp    ) *zt-65.00517_wp ) *zt + 1044.077_wp
305                  zkw= ( ( (-1.361629e-4_wp*zt-1.852732e-2_wp ) *zt-30.41638_wp ) *zt + 2098.925_wp ) *zt+190925.6_wp
306                  zk0= ( zb1*zsr + za1 )*zs + zkw
307                  !
308                  ! masked in situ density anomaly
309                  prd(ji,jj,jk) = (  zrhop / (  1.0_wp - zh / ( zk0 - zh * ( za - zh * zb ) )  )    &
310                     &             - rau0  ) * r1_rau0 * tmask(ji,jj,jk)
311               END DO
312            END DO
313         END DO
314         !
315      CASE( 1 )                !==  Linear formulation = F( temperature )  ==!
316         DO jk = 1, jpkm1
317            prd  (:,:,jk) = ( 0.0285_wp - rn_alpha * pts(:,:,jk,jp_tem) )        * tmask(:,:,jk)
318            prhop(:,:,jk) = ( 1.e0_wp   +            prd (:,:,jk)       ) * rau0 * tmask(:,:,jk)
319         END DO
320         !
321      CASE( 2 )                !==  Linear formulation = F( temperature , salinity )  ==!
322         DO jk = 1, jpkm1
323            prd  (:,:,jk) = ( rn_beta  * pts(:,:,jk,jp_sal) - rn_alpha * pts(:,:,jk,jp_tem) )        * tmask(:,:,jk)
324            prhop(:,:,jk) = ( 1.e0_wp  + prd (:,:,jk) )                                       * rau0 * tmask(:,:,jk)
325         END DO
326         !
327      END SELECT
328      !
329      IF(ln_ctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos-p: ', tab3d_2=prhop, clinfo2=' pot : ', ovlap=1, kdim=jpk )
330      !
331      CALL wrk_dealloc( jpi, jpj, jpk, zws )
332      !
333      IF( nn_timing == 1 ) CALL timing_stop('eos-p')
334      !
335   END SUBROUTINE eos_insitu_pot
336
337
338   SUBROUTINE eos_insitu_2d( pts, pdep, prd )
339      !!----------------------------------------------------------------------
340      !!                  ***  ROUTINE eos_insitu_2d  ***
341      !!
342      !! ** Purpose :   Compute the in situ density (ratio rho/rau0) from
343      !!      potential temperature and salinity using an equation of state
344      !!      defined through the namelist parameter nn_eos. * 2D field case
345      !!
346      !! ** Method :
347      !!      nn_eos = 0 : Jackett and McDougall (1994) equation of state.
348      !!         the in situ density is computed directly as a function of
349      !!         potential temperature relative to the surface (the opa t
350      !!         variable), salt and pressure (assuming no pressure variation
351      !!         along geopotential surfaces, i.e. the pressure p in decibars
352      !!         is approximated by the depth in meters.
353      !!              prd(t,s,p) = ( rho(t,s,p) - rau0 ) / rau0
354      !!         with pressure                      p        decibars
355      !!              potential temperature         t        deg celsius
356      !!              salinity                      s        psu
357      !!              reference volumic mass        rau0     kg/m**3
358      !!              in situ volumic mass          rho      kg/m**3
359      !!              in situ density anomalie      prd      no units
360      !!         Check value: rho = 1060.93298 kg/m**3 for p=10000 dbar,
361      !!          t = 40 deg celcius, s=40 psu
362      !!      nn_eos = 1 : linear equation of state function of temperature only
363      !!              prd(t) = 0.0285 - rn_alpha * t
364      !!      nn_eos = 2 : linear equation of state function of temperature and
365      !!               salinity
366      !!              prd(t,s) = rn_beta * s - rn_alpha * tn - 1.
367      !!      Note that no boundary condition problem occurs in this routine
368      !!      as pts are defined over the whole domain.
369      !!
370      !! ** Action  : - prd , the in situ density (no units)
371      !!
372      !! References :   Jackett and McDougall, J. Atmos. Ocean. Tech., 1994
373      !!----------------------------------------------------------------------
374      !!
375      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celcius]
376      !                                                           ! 2 : salinity               [psu]
377      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) ::   pdep  ! depth                  [m]
378      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(  out) ::   prd   ! in situ density
379      !!
380      INTEGER  ::   ji, jj                    ! dummy loop indices
381      REAL(wp) ::   zt, zs, zh, zsr, zr1, zr2, zr3, zr4, zrhop, ze, zbw   ! temporary scalars
382      REAL(wp) ::   zb, zd, zc, zaw, za, zb1, za1, zkw, zk0, zmask        !    -         -
383      REAL(wp), POINTER, DIMENSION(:,:) :: zws
384      !!----------------------------------------------------------------------
385      !
386      IF( nn_timing == 1 ) CALL timing_start('eos2d')
387      !
388      CALL wrk_alloc( jpi, jpj, zws )
389      !
390
391      prd(:,:) = 0._wp
392
393      SELECT CASE( nn_eos )
394      !
395      CASE( 0 )                !==  Jackett and McDougall (1994) formulation  ==!
396      !
397!CDIR NOVERRCHK
398         DO jj = 1, jpjm1
399!CDIR NOVERRCHK
400            DO ji = 1, fs_jpim1   ! vector opt.
401               zws(ji,jj) = SQRT( ABS( pts(ji,jj,jp_sal) ) )
402            END DO
403         END DO
404         DO jj = 1, jpjm1
405            DO ji = 1, fs_jpim1   ! vector opt.
406               zmask = tmask(ji,jj,1)          ! land/sea bottom mask = surf. mask
407               zt    = pts  (ji,jj,jp_tem)            ! interpolated T
408               zs    = pts  (ji,jj,jp_sal)            ! interpolated S
409               zsr   = zws  (ji,jj)            ! square root of interpolated S
410               zh    = pdep (ji,jj)            ! depth at the partial step level
411               !
412               ! compute volumic mass pure water at atm pressure
413               zr1 = ( ( ( ( 6.536332e-9_wp*zt-1.120083e-6_wp )*zt+1.001685e-4_wp )*zt   &
414                  &                        -9.095290e-3_wp )*zt+6.793952e-2_wp )*zt+999.842594_wp
415               ! seawater volumic mass atm pressure
416               zr2 = ( ( ( 5.3875e-9_wp*zt-8.2467e-7_wp )*zt+7.6438e-5_wp ) *zt   &
417                  &                                   -4.0899e-3_wp ) *zt+0.824493_wp
418               zr3 = ( -1.6546e-6_wp*zt+1.0227e-4_wp ) *zt-5.72466e-3_wp
419               zr4 = 4.8314e-4_wp
420               !
421               ! potential volumic mass (reference to the surface)
422               zrhop= ( zr4*zs + zr3*zsr + zr2 ) *zs + zr1
423               !
424               ! add the compression terms
425               ze = ( -3.508914e-8_wp*zt-1.248266e-8_wp ) *zt-2.595994e-6_wp
426               zbw= (  1.296821e-6_wp*zt-5.782165e-9_wp ) *zt+1.045941e-4_wp
427               zb = zbw + ze * zs
428               !
429               zd =    -2.042967e-2_wp
430               zc =   (-7.267926e-5_wp*zt+2.598241e-3_wp ) *zt+0.1571896_wp
431               zaw= ( ( 5.939910e-6_wp*zt+2.512549e-3_wp ) *zt-0.1028859_wp ) *zt -4.721788_wp
432               za = ( zd*zsr + zc ) *zs + zaw
433               !
434               zb1=     (-0.1909078_wp  *zt+7.390729_wp      ) *zt-55.87545_wp
435               za1=   ( ( 2.326469e-3_wp*zt+1.553190_wp      ) *zt-65.00517_wp ) *zt+1044.077_wp
436               zkw= ( ( (-1.361629e-4_wp*zt-1.852732e-2_wp   ) *zt-30.41638_wp ) *zt   &
437                  &                             +2098.925_wp ) *zt+190925.6_wp
438               zk0= ( zb1*zsr + za1 )*zs + zkw
439               !
440               ! masked in situ density anomaly
441               prd(ji,jj) = ( zrhop / (  1.0_wp - zh / ( zk0 - zh * ( za - zh * zb ) )  ) - rau0 ) / rau0 * zmask
442            END DO
443         END DO
444         !
445      CASE( 1 )                !==  Linear formulation = F( temperature )  ==!
446         DO jj = 1, jpjm1
447            DO ji = 1, fs_jpim1   ! vector opt.
448               prd(ji,jj) = ( 0.0285_wp - rn_alpha * pts(ji,jj,jp_tem) ) * tmask(ji,jj,1)
449            END DO
450         END DO
451         !
452      CASE( 2 )                !==  Linear formulation = F( temperature , salinity )  ==!
453         DO jj = 1, jpjm1
454            DO ji = 1, fs_jpim1   ! vector opt.
455               prd(ji,jj) = ( rn_beta * pts(ji,jj,jp_sal) - rn_alpha * pts(ji,jj,jp_tem) ) * tmask(ji,jj,1)
456            END DO
457         END DO
458         !
459      END SELECT
460
461      IF(ln_ctl)   CALL prt_ctl( tab2d_1=prd, clinfo1=' eos2d: ' )
462      !
463      CALL wrk_dealloc( jpi, jpj, zws )
464      !
465      IF( nn_timing == 1 ) CALL timing_stop('eos2d')
466      !
467   END SUBROUTINE eos_insitu_2d
468
469
470   SUBROUTINE eos_bn2( pts, pn2 )
471      !!----------------------------------------------------------------------
472      !!                  ***  ROUTINE eos_bn2  ***
473      !!
474      !! ** Purpose :   Compute the local Brunt-Vaisala frequency at the time-
475      !!      step of the input arguments
476      !!
477      !! ** Method :
478      !!       * nn_eos = 0  : UNESCO sea water properties
479      !!         The brunt-vaisala frequency is computed using the polynomial
480      !!      polynomial expression of McDougall (1987):
481      !!            N^2 = grav * beta * ( alpha/beta*dk[ t ] - dk[ s ] )/e3w
482      !!      If lk_zdfddm=T, the heat/salt buoyancy flux ratio Rrau is
483      !!      computed and used in zdfddm module :
484      !!              Rrau = alpha/beta * ( dk[ t ] / dk[ s ] )
485      !!       * nn_eos = 1  : linear equation of state (temperature only)
486      !!            N^2 = grav * rn_alpha * dk[ t ]/e3w
487      !!       * nn_eos = 2  : linear equation of state (temperature & salinity)
488      !!            N^2 = grav * (rn_alpha * dk[ t ] - rn_beta * dk[ s ] ) / e3w
489      !!      The use of potential density to compute N^2 introduces e r r o r
490      !!      in the sign of N^2 at great depths. We recommand the use of
491      !!      nn_eos = 0, except for academical studies.
492      !!        Macro-tasked on horizontal slab (jk-loop)
493      !!      N.B. N^2 is set to zero at the first level (JK=1) in inidtr
494      !!      and is never used at this level.
495      !!
496      !! ** Action  : - pn2 : the brunt-vaisala frequency
497      !!
498      !! References :   McDougall, J. Phys. Oceanogr., 17, 1950-1964, 1987.
499      !!----------------------------------------------------------------------
500      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celcius]
501      !                                                               ! 2 : salinity               [psu]
502      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pn2   ! Brunt-Vaisala frequency    [s-1]
503      !!
504      INTEGER  ::   ji, jj, jk   ! dummy loop indices
505      REAL(wp) ::   zgde3w, zt, zs, zh, zalbet, zbeta   ! local scalars
506#if defined key_zdfddm
507      REAL(wp) ::   zds   ! local scalars
508#endif
509      !!----------------------------------------------------------------------
510
511      !
512      IF( nn_timing == 1 ) CALL timing_start('bn2')
513      !
514      ! pn2 : interior points only (2=< jk =< jpkm1 )
515      ! --------------------------
516      !
517      SELECT CASE( nn_eos )
518      !
519      CASE( 0 )                !==  Jackett and McDougall (1994) formulation  ==!
520         DO jk = 2, jpkm1
521            DO jj = 1, jpj
522               DO ji = 1, jpi
523                  zgde3w = grav / fse3w(ji,jj,jk)
524                  zt = 0.5 * ( pts(ji,jj,jk,jp_tem) + pts(ji,jj,jk-1,jp_tem) )         ! potential temperature at w-pt
525                  zs = 0.5 * ( pts(ji,jj,jk,jp_sal) + pts(ji,jj,jk-1,jp_sal) ) - 35.0  ! salinity anomaly (s-35) at w-pt
526                  zh = fsdepw(ji,jj,jk)                                                ! depth in meters  at w-point
527                  !
528                  zalbet = ( ( ( - 0.255019e-07_wp * zt + 0.298357e-05_wp ) * zt   &   ! ratio alpha/beta
529                     &                                  - 0.203814e-03_wp ) * zt   &
530                     &                                  + 0.170907e-01_wp ) * zt   &
531                     &   +         0.665157e-01_wp                                 &
532                     &   +     ( - 0.678662e-05_wp * zs                            &
533                     &           - 0.846960e-04_wp * zt + 0.378110e-02_wp ) * zs   &
534                     &   +   ( ( - 0.302285e-13_wp * zh                            &
535                     &           - 0.251520e-11_wp * zs                            &
536                     &           + 0.512857e-12_wp * zt * zt              ) * zh   &
537                     &           - 0.164759e-06_wp * zs                            &
538                     &        +(   0.791325e-08_wp * zt - 0.933746e-06_wp ) * zt   &
539                     &                                  + 0.380374e-04_wp ) * zh
540                     !
541                  zbeta  = ( ( -0.415613e-09_wp * zt + 0.555579e-07_wp ) * zt      &   ! beta
542                     &                               - 0.301985e-05_wp ) * zt      &
543                     &   +       0.785567e-03_wp                                   &
544                     &   + (     0.515032e-08_wp * zs                              &
545                     &         + 0.788212e-08_wp * zt - 0.356603e-06_wp ) * zs     &
546                     &   + ( (   0.121551e-17_wp * zh                              &
547                     &         - 0.602281e-15_wp * zs                              &
548                     &         - 0.175379e-14_wp * zt + 0.176621e-12_wp ) * zh     &
549                     &                                + 0.408195e-10_wp   * zs     &
550                     &     + ( - 0.213127e-11_wp * zt + 0.192867e-09_wp ) * zt     &
551                     &                                - 0.121555e-07_wp ) * zh
552                     !
553                  pn2(ji,jj,jk) = zgde3w * zbeta * tmask(ji,jj,jk)           &   ! N^2
554                     &          * ( zalbet * ( pts(ji,jj,jk-1,jp_tem) - pts(ji,jj,jk,jp_tem) )   &
555                     &                     - ( pts(ji,jj,jk-1,jp_sal) - pts(ji,jj,jk,jp_sal) ) )
556#if defined key_zdfddm
557                  !                                                         !!bug **** caution a traiter zds=dk[S]= 0 !!!!
558                  zds = ( pts(ji,jj,jk-1,jp_sal) - pts(ji,jj,jk,jp_sal) )                    ! Rrau = (alpha / beta) (dk[t] / dk[s])
559                  IF ( ABS( zds) <= 1.e-20_wp ) zds = 1.e-20_wp
560                  rrau(ji,jj,jk) = zalbet * ( pts(ji,jj,jk-1,jp_tem) - pts(ji,jj,jk,jp_tem) ) / zds
561#endif
562               END DO
563            END DO
564         END DO
565         !
566      CASE( 1 )                !==  Linear formulation = F( temperature )  ==!
567         DO jk = 2, jpkm1
568            pn2(:,:,jk) = grav * rn_alpha * ( pts(:,:,jk-1,jp_tem) - pts(:,:,jk,jp_tem) ) / fse3w(:,:,jk) * tmask(:,:,jk)
569         END DO
570         !
571      CASE( 2 )                !==  Linear formulation = F( temperature , salinity )  ==!
572         DO jk = 2, jpkm1
573            pn2(:,:,jk) = grav * (  rn_alpha * ( pts(:,:,jk-1,jp_tem) - pts(:,:,jk,jp_tem) )      &
574               &                  - rn_beta  * ( pts(:,:,jk-1,jp_sal) - pts(:,:,jk,jp_sal) )  )   &
575               &               / fse3w(:,:,jk) * tmask(:,:,jk)
576         END DO
577#if defined key_zdfddm
578         DO jk = 2, jpkm1                                 ! Rrau = (alpha / beta) (dk[t] / dk[s])
579            DO jj = 1, jpj
580               DO ji = 1, jpi
581                  zds = ( pts(ji,jj,jk-1,jp_sal) - pts(ji,jj,jk,jp_sal) )
582                  IF ( ABS( zds ) <= 1.e-20_wp ) zds = 1.e-20_wp
583                  rrau(ji,jj,jk) = ralpbet * ( pts(ji,jj,jk-1,jp_tem) - pts(ji,jj,jk,jp_tem) ) / zds
584               END DO
585            END DO
586         END DO
587#endif
588      END SELECT
589
590      IF(ln_ctl)   CALL prt_ctl( tab3d_1=pn2, clinfo1=' bn2  : ', ovlap=1, kdim=jpk )
591#if defined key_zdfddm
592      IF(ln_ctl)   CALL prt_ctl( tab3d_1=rrau, clinfo1=' rrau : ', ovlap=1, kdim=jpk )
593#endif
594      !
595      IF( nn_timing == 1 ) CALL timing_stop('bn2')
596      !
597   END SUBROUTINE eos_bn2
598
599
600   SUBROUTINE eos_alpbet( pts, palpbet, beta0 )
601      !!----------------------------------------------------------------------
602      !!                 ***  ROUTINE eos_alpbet  ***
603      !!
604      !! ** Purpose :   Calculates the in situ thermal/haline expansion ratio at T-points
605      !!
606      !! ** Method  :   calculates alpha / beta ratio at T-points
607      !!       * nn_eos = 0  : UNESCO sea water properties
608      !!                       The alpha/beta ratio is returned as 3-D array palpbet using the polynomial
609      !!                       polynomial expression of McDougall (1987).
610      !!                       Scalar beta0 is returned = 1.
611      !!       * nn_eos = 1  : linear equation of state (temperature only)
612      !!                       The ratio is undefined, so we return alpha as palpbet
613      !!                       Scalar beta0 is returned = 0.
614      !!       * nn_eos = 2  : linear equation of state (temperature & salinity)
615      !!                       The alpha/beta ratio is returned as ralpbet
616      !!                       Scalar beta0 is returned = 1.
617      !!
618      !! ** Action  : - palpbet : thermal/haline expansion ratio at T-points
619      !!            :   beta0   : 1. or 0.
620      !!----------------------------------------------------------------------
621      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts       ! pot. temperature & salinity
622      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   palpbet   ! thermal/haline expansion ratio
623      REAL(wp),                              INTENT(  out) ::   beta0     ! set = 1 except with case 1 eos, rho=rho(T)
624      !!
625      INTEGER  ::   ji, jj, jk   ! dummy loop indices
626      REAL(wp) ::   zt, zs, zh   ! local scalars
627      !!----------------------------------------------------------------------
628      !
629      IF( nn_timing == 1 ) CALL timing_start('eos_alpbet')
630      !
631      SELECT CASE ( nn_eos )
632      !
633      CASE ( 0 )               ! Jackett and McDougall (1994) formulation
634         DO jk = 1, jpk
635            DO jj = 1, jpj
636               DO ji = 1, jpi
637                  zt = pts(ji,jj,jk,jp_tem)           ! potential temperature
638                  zs = pts(ji,jj,jk,jp_sal) - 35._wp  ! salinity anomaly (s-35)
639                  zh = fsdept(ji,jj,jk)               ! depth in meters
640                  !
641                  palpbet(ji,jj,jk) =                                              &
642                     &     ( ( ( - 0.255019e-07_wp * zt + 0.298357e-05_wp ) * zt   &
643                     &                                  - 0.203814e-03_wp ) * zt   &
644                     &                                  + 0.170907e-01_wp ) * zt   &
645                     &   + 0.665157e-01_wp                                         &
646                     &   +     ( - 0.678662e-05_wp * zs                            &
647                     &           - 0.846960e-04_wp * zt + 0.378110e-02_wp ) * zs   &
648                     &   +   ( ( - 0.302285e-13_wp * zh                            &
649                     &           - 0.251520e-11_wp * zs                            &
650                     &           + 0.512857e-12_wp * zt * zt              ) * zh   &
651                     &           - 0.164759e-06_wp * zs                            &
652                     &        +(   0.791325e-08_wp * zt - 0.933746e-06_wp ) * zt   &
653                     &                                  + 0.380374e-04_wp ) * zh
654               END DO
655            END DO
656         END DO
657         beta0 = 1._wp
658         !
659      CASE ( 1 )              !==  Linear formulation = F( temperature )  ==!
660         palpbet(:,:,:) = rn_alpha
661         beta0 = 0._wp
662         !
663      CASE ( 2 )              !==  Linear formulation = F( temperature , salinity )  ==!
664         palpbet(:,:,:) = ralpbet
665         beta0 = 1._wp
666         !
667      CASE DEFAULT
668         IF(lwp) WRITE(numout,cform_err)
669         IF(lwp) WRITE(numout,*) '          bad flag value for nn_eos = ', nn_eos
670         nstop = nstop + 1
671         !
672      END SELECT
673      !
674      IF( nn_timing == 1 ) CALL timing_stop('eos_alpbet')
675      !
676   END SUBROUTINE eos_alpbet
677
678
679   FUNCTION tfreez( psal, pdep ) RESULT( ptf )
680      !!----------------------------------------------------------------------
681      !!                 ***  ROUTINE eos_init  ***
682      !!
683      !! ** Purpose :   Compute the sea surface freezing temperature [Celcius]
684      !!
685      !! ** Method  :   UNESCO freezing point at the surface (pressure = 0???)
686      !!       freezing point [Celcius]=(-.0575+1.710523e-3*sqrt(abs(s))-2.154996e-4*s)*s-7.53e-4*p
687      !!       checkvalue: tf= -2.588567 Celsius for s=40.0psu, p=500. decibars
688      !!
689      !! Reference  :   UNESCO tech. papers in the marine science no. 28. 1978
690      !!----------------------------------------------------------------------
691      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   psal   ! salinity             [psu]
692      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ), OPTIONAL ::   pdep   ! depth      [decibars]
693      ! Leave result array automatic rather than making explicitly allocated
694      REAL(wp), DIMENSION(jpi,jpj)                ::   ptf    ! freezing temperature [Celcius]
695      !!----------------------------------------------------------------------
696      !
697      ptf(:,:) = ( - 0.0575_wp + 1.710523e-3_wp * SQRT( psal(:,:) )   &
698         &                     - 2.154996e-4_wp *       psal(:,:)   ) * psal(:,:)
699      IF ( PRESENT( pdep ) ) THEN   
700         ptf(:,:) = ptf(:,:) - 7.53e-4_wp * pdep(:,:)
701      ENDIF
702      !
703   END FUNCTION tfreez
704
705
706   SUBROUTINE eos_init
707      !!----------------------------------------------------------------------
708      !!                 ***  ROUTINE eos_init  ***
709      !!
710      !! ** Purpose :   initializations for the equation of state
711      !!
712      !! ** Method  :   Read the namelist nameos and control the parameters
713      !!----------------------------------------------------------------------
714      NAMELIST/nameos/ nn_eos, rn_alpha, rn_beta
715      !!----------------------------------------------------------------------
716      INTEGER  ::   ios
717      !
718      REWIND( numnam_ref )              ! Namelist nameos in reference namelist : equation of state
719      READ  ( numnam_ref, nameos, IOSTAT = ios, ERR = 901 )
720901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nameos in reference namelist', lwp )
721
722      REWIND( numnam_cfg )              ! Namelist nameos in configuration namelist : equation of state
723      READ  ( numnam_cfg, nameos, IOSTAT = ios, ERR = 902 )
724902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nameos in configuration namelist', lwp )
725      IF(lwm) WRITE( numond, nameos )
726      !
727      IF(lwp) THEN                ! Control print
728         WRITE(numout,*)
729         WRITE(numout,*) 'eos_init : equation of state'
730         WRITE(numout,*) '~~~~~~~~'
731         WRITE(numout,*) '          Namelist nameos : set eos parameters'
732         WRITE(numout,*) '             flag for eq. of state and N^2  nn_eos   = ', nn_eos
733         WRITE(numout,*) '             thermal exp. coef. (linear)    rn_alpha = ', rn_alpha
734         WRITE(numout,*) '             saline  exp. coef. (linear)    rn_beta  = ', rn_beta
735      ENDIF
736      !
737      SELECT CASE( nn_eos )         ! check option
738      !
739      CASE( 0 )                        !==  Jackett and McDougall (1994) formulation  ==!
740         IF(lwp) WRITE(numout,*)
741         IF(lwp) WRITE(numout,*) '          use of Jackett & McDougall (1994) equation of state and'
742         IF(lwp) WRITE(numout,*) '                 McDougall (1987) Brunt-Vaisala frequency'
743         !
744      CASE( 1 )                        !==  Linear formulation = F( temperature )  ==!
745         IF(lwp) WRITE(numout,*)
746         IF(lwp) WRITE(numout,*) '          use of linear eos rho(T) = rau0 * ( 1.0285 - rn_alpha * T )'
747         IF( lk_zdfddm ) CALL ctl_stop( '          double diffusive mixing parameterization requires',   &
748              &                         ' that T and S are used as state variables' )
749         !
750      CASE( 2 )                        !==  Linear formulation = F( temperature , salinity )  ==!
751         ralpbet = rn_alpha / rn_beta
752         IF(lwp) WRITE(numout,*)
753         IF(lwp) WRITE(numout,*) '          use of linear eos rho(T,S) = rau0 * ( rn_beta * S - rn_alpha * T )'
754         !
755      CASE DEFAULT                     !==  ERROR in nn_eos  ==!
756         WRITE(ctmp1,*) '          bad flag value for nn_eos = ', nn_eos
757         CALL ctl_stop( ctmp1 )
758         !
759      END SELECT
760      !
761   END SUBROUTINE eos_init
762
763   !!======================================================================
764END MODULE eosbn2
Note: See TracBrowser for help on using the repository browser.