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/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

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