New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
eosbn2.F90 in branches/TAM_V3_0/NEMO/OPA_SRC – NEMO

source: branches/TAM_V3_0/NEMO/OPA_SRC/eosbn2.F90 @ 1884

Last change on this file since 1884 was 1884, checked in by rblod, 14 years ago

Light adaptation of NEMO direct model routine to handle TAM

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