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 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

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