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

Last change on this file since 941 was 920, checked in by rblod, 16 years ago

Correct incompatibilities with Agrif (easier part), see ticket #133

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