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

source: trunk/NEMO/OPA_SRC/eosbn2.F90 @ 1587

Last change on this file since 1587 was 1559, checked in by ctlod, 15 years ago

only cosmetic changes

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