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.
isfcavgam.F90 in NEMO/branches/2020/r12377_ticket2386/tests/ISOMIP+/MY_SRC – NEMO

source: NEMO/branches/2020/r12377_ticket2386/tests/ISOMIP+/MY_SRC/isfcavgam.F90 @ 13694

Last change on this file since 13694 was 13694, checked in by andmirek, 3 years ago

Ticket #2386: merge with trunk rev 13688

File size: 12.8 KB
Line 
1MODULE isfcavgam
2   !!======================================================================
3   !!                       ***  MODULE  isfgammats  ***
4   !! Ice shelf gamma module :  compute exchange coeficient at the ice/ocean interface
5   !!======================================================================
6   !! History :  4.1  !  (P. Mathiot) original
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   isfcav_gammats       : compute exchange coeficient gamma
11   !!----------------------------------------------------------------------
12   USE isf_oce
13   USE isfutils, ONLY: debug
14   USE isftbl  , ONLY: isf_tbl
15
16   USE oce     , ONLY: uu, vv, rn2         ! ocean dynamics and tracers
17   USE phycst  , ONLY: grav, vkarmn        ! physical constant
18   USE eosbn2  , ONLY: eos_rab             ! equation of state
19   USE zdfdrg  , ONLY: rCd0_top, r_ke0_top ! vertical physics: top/bottom drag coef.
20   USE iom     , ONLY: iom_put             !
21   USE lib_mpp , ONLY: ctl_stop
22
23   USE dom_oce        ! ocean space and time domain
24   USE in_out_manager ! I/O manager
25   !
26   IMPLICIT NONE
27   !
28   PRIVATE
29   !
30   PUBLIC   isfcav_gammats
31
32#  include "domzgr_substitute.h90"
33   !!----------------------------------------------------------------------
34   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
35   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
36   !! Software governed by the CeCILL license (see ./LICENSE)
37   !!----------------------------------------------------------------------
38CONTAINS
39   !
40   !!-----------------------------------------------------------------------------------------------------
41   !!                              PUBLIC SUBROUTINES
42   !!-----------------------------------------------------------------------------------------------------
43   !
44   SUBROUTINE isfcav_gammats( Kmm, pttbl, pstbl, pqoce, pqfwf, pgt, pgs )
45      !!----------------------------------------------------------------------
46      !! ** Purpose    : compute the coefficient echange for heat and fwf flux
47      !!
48      !! ** Method     : select the gamma formulation
49      !!                 3 method available (cst, vel and vel_stab)
50      !!---------------------------------------------------------------------
51      !!-------------------------- OUT -------------------------------------
52      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pgt  , pgs      ! gamma t and gamma s
53      !!-------------------------- IN  -------------------------------------
54      INTEGER                                     :: Kmm             ! ocean time level index
55      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pqoce, pqfwf    ! isf heat and fwf
56      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pttbl, pstbl    ! top boundary layer tracer
57      !!---------------------------------------------------------------------
58      REAL(wp), DIMENSION(jpi,jpj)                :: zutbl, zvtbl    ! top boundary layer velocity
59      !!---------------------------------------------------------------------
60      !
61      !==========================================
62      ! 1.: compute velocity in the tbl if needed
63      !==========================================
64      !
65      SELECT CASE ( cn_gammablk )
66      CASE ( 'spe'  ) 
67         ! gamma is constant (specified in namelist)
68         ! nothing to do
69      CASE ('vel', 'vel_stab')
70         ! compute velocity in tbl
71         CALL isf_tbl(Kmm, uu(:,:,:,Kmm) ,zutbl(:,:),'U', miku, rhisf_tbl_cav)
72         CALL isf_tbl(Kmm, vv(:,:,:,Kmm) ,zvtbl(:,:),'V', mikv, rhisf_tbl_cav)
73         !
74         ! mask velocity in tbl with ice shelf mask
75         zutbl(:,:) = zutbl(:,:) * mskisf_cav(:,:)
76         zvtbl(:,:) = zvtbl(:,:) * mskisf_cav(:,:)
77         !
78         ! output
79         CALL iom_put('utbl',zutbl(:,:))
80         CALL iom_put('vtbl',zvtbl(:,:))
81      CASE DEFAULT
82         CALL ctl_stop('STOP','method to compute gamma (cn_gammablk) is unknown (should not see this)')
83      END SELECT
84      !
85      !==========================================
86      ! 2.: compute gamma
87      !==========================================
88      !
89      SELECT CASE ( cn_gammablk )
90      CASE ( 'spe'  ) ! gamma is constant (specified in namelist)
91         pgt(:,:) = rn_gammat0
92         pgs(:,:) = rn_gammas0
93      CASE ( 'vel' ) ! gamma is proportional to u*
94         CALL gammats_vel      (                   zutbl, zvtbl, rCd0_top, rn_vtide**2,               pgt, pgs )
95      CASE ( 'vel_stab' ) ! gamma depends of stability of boundary layer and u*
96         CALL gammats_vel_stab (Kmm, pttbl, pstbl, zutbl, zvtbl, rCd0_top, rn_vtide**2, pqoce, pqfwf, pgt, pgs )
97      CASE DEFAULT
98         CALL ctl_stop('STOP','method to compute gamma (cn_gammablk) is unknown (should not see this)')
99      END SELECT
100      !
101      !==========================================
102      ! 3.: output and debug
103      !==========================================
104      !
105      CALL iom_put('isfgammat', pgt(:,:))
106      CALL iom_put('isfgammas', pgs(:,:))
107      !
108      IF (ln_isfdebug) THEN
109         CALL debug( 'isfcav_gam pgt:', pgt(:,:) )
110         CALL debug( 'isfcav_gam pgs:', pgs(:,:) )
111      END IF
112      !
113   END SUBROUTINE isfcav_gammats
114   !
115   !!-----------------------------------------------------------------------------------------------------
116   !!                              PRIVATE SUBROUTINES
117   !!-----------------------------------------------------------------------------------------------------
118   !
119   SUBROUTINE gammats_vel( putbl, pvtbl, pCd, pke2, &   ! <<== in
120      &                                  pgt, pgs   )   ! ==>> out gammats [m/s]
121      !!----------------------------------------------------------------------
122      !! ** Purpose    : compute the coefficient echange coefficient
123      !!
124      !! ** Method     : gamma is velocity dependent ( gt= gt0 * Ustar )
125      !!
126      !! ** Reference  : Asay-Davis et al., Geosci. Model Dev., 9, 2471-2497, 2016
127      !!---------------------------------------------------------------------
128      !!-------------------------- OUT -------------------------------------
129      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pgt, pgs     ! gammat and gammas [m/s]
130      !!-------------------------- IN  -------------------------------------
131      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: putbl, pvtbl ! velocity in the losch top boundary layer
132      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pCd          ! drag coefficient
133      REAL(wp),                     INTENT(in   ) :: pke2         ! background velocity
134      !!---------------------------------------------------------------------
135      REAL(wp), DIMENSION(jpi,jpj) :: zustar
136      !!---------------------------------------------------------------------
137      !
138      ! compute ustar (AD15 eq. 27)
139      zustar(:,:) = SQRT( pCd(:,:) * ( putbl(:,:) * putbl(:,:) + pvtbl(:,:) * pvtbl(:,:) + pke2 ) ) * mskisf_cav(:,:)
140      !
141      ! Compute gammats
142      pgt(:,:) = zustar(:,:) * rn_gammat0
143      pgs(:,:) = zustar(:,:) * rn_gammas0
144      !
145      ! output ustar
146      CALL iom_put('isfustar',zustar(:,:))
147      !
148   END SUBROUTINE gammats_vel
149
150   SUBROUTINE gammats_vel_stab( Kmm, pttbl, pstbl, putbl, pvtbl, pCd, pke2, pqoce, pqfwf, &  ! <<== in
151      &                                                                     pgt  , pgs    )  ! ==>> out gammats [m/s]
152      !!----------------------------------------------------------------------
153      !! ** Purpose    : compute the coefficient echange coefficient
154      !!
155      !! ** Method     : gamma is velocity dependent and stability dependent
156      !!
157      !! ** Reference  : Holland and Jenkins, 1999, JPO, p1787-1800
158      !!---------------------------------------------------------------------
159      !!-------------------------- OUT -------------------------------------
160      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pgt, pgs     ! gammat and gammas
161      !!-------------------------- IN  -------------------------------------
162      INTEGER                                     :: Kmm            ! ocean time level index
163      REAL(wp),                     INTENT(in   ) :: pke2           ! background velocity squared
164      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pqoce, pqfwf   ! surface heat flux and fwf flux
165      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pCd            ! drag coeficient
166      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: putbl, pvtbl   ! velocity in the losch top boundary layer
167      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pttbl, pstbl   ! tracer   in the losch top boundary layer
168      !!---------------------------------------------------------------------
169      INTEGER  :: ji, jj                     ! loop index
170      INTEGER  :: ikt                        ! local integer
171      REAL(wp) :: zdku, zdkv                 ! U, V shear
172      REAL(wp) :: zPr, zSc, zRc              ! Prandtl, Scmidth and Richardson number
173      REAL(wp) :: zmob, zmols                ! Monin Obukov length, coriolis factor at T point
174      REAL(wp) :: zbuofdep, zhnu             ! Bouyancy length scale, sublayer tickness
175      REAL(wp) :: zhmax                      ! limitation of mol
176      REAL(wp) :: zetastar                   ! stability parameter
177      REAL(wp) :: zgmolet, zgmoles, zgturb   ! contribution of modelecular sublayer and turbulence
178      REAL(wp) :: zcoef                      ! temporary coef
179      REAL(wp) :: zdep
180      REAL(wp) :: zeps = 1.0e-20_wp   
181      REAL(wp), PARAMETER :: zxsiN = 0.052_wp   ! dimensionless constant
182      REAL(wp), PARAMETER :: znu   = 1.95e-6_wp ! kinamatic viscosity of sea water (m2.s-1)
183      REAL(wp), DIMENSION(2) :: zts, zab
184      REAL(wp), DIMENSION(jpi,jpj) :: zustar    ! friction velocity
185      !!---------------------------------------------------------------------
186      !
187      ! compute ustar
188      zustar(:,:) = SQRT( pCd * ( putbl(:,:) * putbl(:,:) + pvtbl(:,:) * pvtbl(:,:) + pke2 ) )
189      !
190      ! output ustar
191      CALL iom_put('isfustar',zustar(:,:))
192      !
193      ! compute Pr and Sc number (eq ??)
194      zPr =   13.8_wp
195      zSc = 2432.0_wp
196      !
197      ! compute gamma mole (eq ??)
198      zgmolet = 12.5_wp * zPr ** (2.0/3.0) - 6.0_wp
199      zgmoles = 12.5_wp * zSc ** (2.0/3.0) - 6.0_wp
200      !
201      ! compute gamma
202      DO ji = 2, jpi
203         DO jj = 2, jpj
204            ikt = mikt(ji,jj)
205
206            IF( zustar(ji,jj) == 0._wp ) THEN           ! only for kt = 1 I think
207               pgt = rn_gammat0
208               pgs = rn_gammas0
209            ELSE
210               ! compute Rc number (as done in zdfric.F90)
211!!gm better to do it like in the new zdfric.F90   i.e. avm weighted Ri computation
212               zcoef = 0.5_wp / e3w(ji,jj,ikt+1,Kmm)
213               !                                            ! shear of horizontal velocity
214               zdku = zcoef * (  uu(ji-1,jj  ,ikt  ,Kmm) + uu(ji,jj,ikt  ,Kmm)  &
215                  &             -uu(ji-1,jj  ,ikt+1,Kmm) - uu(ji,jj,ikt+1,Kmm)  )
216               zdkv = zcoef * (  vv(ji  ,jj-1,ikt  ,Kmm) + vv(ji,jj,ikt  ,Kmm)  &
217                  &             -vv(ji  ,jj-1,ikt+1,Kmm) - vv(ji,jj,ikt+1,Kmm)  )
218               !                                            ! richardson number (minimum value set to zero)
219               zRc = MAX(rn2(ji,jj,ikt+1), 0._wp) / MAX( zdku*zdku + zdkv*zdkv, zeps )
220
221               ! compute bouyancy
222               zts(jp_tem) = pttbl(ji,jj)
223               zts(jp_sal) = pstbl(ji,jj)
224               zdep        = gdepw(ji,jj,ikt,Kmm)
225               !
226               CALL eos_rab( zts, zdep, zab, Kmm )
227               !
228               ! compute length scale (Eq ??)
229               zbuofdep = grav * ( zab(jp_tem) * pqoce(ji,jj) - zab(jp_sal) * pqfwf(ji,jj) )
230               !
231               ! compute Monin Obukov Length
232               ! Maximum boundary layer depth (Eq ??)
233               zhmax = gdept(ji,jj,mbkt(ji,jj),Kmm) - gdepw(ji,jj,mikt(ji,jj),Kmm) -0.001_wp
234               !
235               ! Compute Monin obukhov length scale at the surface and Ekman depth: (Eq ??)
236               zmob   = zustar(ji,jj) ** 3 / (vkarmn * (zbuofdep + zeps))
237               zmols  = SIGN(1._wp, zmob) * MIN(ABS(zmob), zhmax) * tmask(ji,jj,ikt)
238               !
239               ! compute eta* (stability parameter) (Eq ??)
240               zetastar = 1._wp / ( SQRT(1._wp + MAX(zxsiN * zustar(ji,jj) / ( ABS(ff_f(ji,jj)) * zmols * zRc ), 0._wp)))
241               !
242               ! compute the sublayer thickness (Eq ??)
243               zhnu = 5 * znu / zustar(ji,jj)
244               !
245               ! compute gamma turb (Eq ??)
246               zgturb = 1._wp / vkarmn * LOG(zustar(ji,jj) * zxsiN * zetastar * zetastar / ( ABS(ff_f(ji,jj)) * zhnu )) &
247               &      + 1._wp / ( 2 * zxsiN * zetastar ) - 1._wp / vkarmn
248               !
249               ! compute gammats
250               pgt(ji,jj) = zustar(ji,jj) / (zgturb + zgmolet)
251               pgs(ji,jj) = zustar(ji,jj) / (zgturb + zgmoles)
252            END IF
253         END DO
254      END DO
255
256   END SUBROUTINE gammats_vel_stab
257
258END MODULE isfcavgam
Note: See TracBrowser for help on using the repository browser.