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

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

CT : UPDATE123 : change indices of the SUM control step for the eos2d(:,) array

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