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 branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90 @ 3326

Last change on this file since 3326 was 3326, checked in by gm, 12 years ago

Ediag branche: #927 add Potential Energy trend diagnostics (trdpen.F90)

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