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.
sbcisf.F90 in branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcisf.F90 @ 9168

Last change on this file since 9168 was 9168, checked in by gm, 6 years ago

dev_merge_2017: OPA_SRC & CONFIG: remove useless warning when reading namelist_cfg

  • Property svn:keywords set to Id
File size: 44.7 KB
Line 
1MODULE sbcisf
2   !!======================================================================
3   !!                       ***  MODULE  sbcisf  ***
4   !! Surface module :  update surface ocean boundary condition under ice
5   !!                   shelf
6   !!======================================================================
7   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
8   !!            X.X  !  2006-02  (C. Wang   ) Original code bg03
9   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   sbc_isf       : update sbc under ice shelf
14   !!----------------------------------------------------------------------
15   USE oce            ! ocean dynamics and tracers
16   USE dom_oce        ! ocean space and time domain
17   USE phycst         ! physical constants
18   USE eosbn2         ! equation of state
19   USE sbc_oce        ! surface boundary condition: ocean fields
20   USE zdfdrg         ! vertical physics: top/bottom drag coef.
21   !
22   USE in_out_manager ! I/O manager
23   USE iom            ! I/O library
24   USE fldread        ! read input field at current time step
25   USE lbclnk         !
26   USE lib_fortran    ! glob_sum
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   sbc_isf, sbc_isf_init, sbc_isf_div, sbc_isf_alloc  ! routine called in sbcmod and divhor
32
33   ! public in order to be able to output then
34
35   REAL(wp), PUBLIC ::   rn_hisf_tbl                 !: thickness of top boundary layer [m]
36   INTEGER , PUBLIC ::   nn_isf                      !: flag to choose between explicit/param/specified 
37   INTEGER , PUBLIC ::   nn_isfblk                   !: flag to choose the bulk formulation to compute the ice shelf melting
38   INTEGER , PUBLIC ::   nn_gammablk                 !: flag to choose how the exchange coefficient is computed
39   REAL(wp), PUBLIC ::   rn_gammat0                  !: temperature exchange coeficient []
40   REAL(wp), PUBLIC ::   rn_gammas0                  !: salinity    exchange coeficient []
41
42   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   misfkt   , misfkb        !: Level of ice shelf base
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rzisf_tbl                !: depth of calving front (shallowest point) nn_isf ==2/3
44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf_tbl, rhisf_tbl_0   !: thickness of tbl  [m]
45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   r1_hisf_tbl              !: 1/thickness of tbl
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ralpha                   !: proportion of bottom cell influenced by tbl
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   risfLeff                 !: effective length (Leff) BG03 nn_isf==2
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ttbl, stbl, utbl, vtbl   !: top boundary layer variable at T point
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qisf                     !: net heat flux from ice shelf      [W/m2]
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   risf_tsc_b, risf_tsc     !: before and now T & S isf contents [K.m/s & PSU.m/s] 
51
52   LOGICAL, PUBLIC ::   l_isfcpl = .false.       !: isf recieved from oasis
53
54   REAL(wp), PUBLIC, SAVE ::   rcpi     = 2000.0_wp     !: specific heat of ice shelf             [J/kg/K]
55   REAL(wp), PUBLIC, SAVE ::   rkappa   = 1.54e-6_wp    !: heat diffusivity through the ice-shelf [m2/s]
56   REAL(wp), PUBLIC, SAVE ::   rhoisf   = 920.0_wp      !: volumic mass of ice shelf              [kg/m3]
57   REAL(wp), PUBLIC, SAVE ::   tsurf    = -20.0_wp      !: air temperature on top of ice shelf    [C]
58   REAL(wp), PUBLIC, SAVE ::   rlfusisf = 0.334e6_wp    !: latent heat of fusion of ice shelf     [J/kg]
59
60!: Variable used in fldread to read the forcing file (nn_isf == 4 .OR. nn_isf == 3)
61   CHARACTER(len=100), PUBLIC           :: cn_dirisf  = './' !: Root directory for location of ssr files
62   TYPE(FLD_N)       , PUBLIC           :: sn_fwfisf         !: information about the isf melting file to be read
63   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_fwfisf
64   TYPE(FLD_N)       , PUBLIC           :: sn_rnfisf         !: information about the isf melting param.   file to be read
65   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_rnfisf           
66   TYPE(FLD_N)       , PUBLIC           :: sn_depmax_isf     !: information about the grounding line depth file to be read
67   TYPE(FLD_N)       , PUBLIC           :: sn_depmin_isf     !: information about the calving   line depth file to be read
68   TYPE(FLD_N)       , PUBLIC           :: sn_Leff_isf       !: information about the effective length     file to be read
69   
70   !!----------------------------------------------------------------------
71   !! NEMO/OPA 4.0 , LOCEAN-IPSL (2017)
72   !! $Id$
73   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
74   !!----------------------------------------------------------------------
75CONTAINS
76 
77  SUBROUTINE sbc_isf( kt )
78      !!---------------------------------------------------------------------
79      !!                  ***  ROUTINE sbc_isf  ***
80      !!
81      !! ** Purpose : Compute Salt and Heat fluxes related to ice_shelf
82      !!              melting and freezing
83      !!
84      !! ** Method  :  4 parameterizations are available according to nn_isf
85      !!               nn_isf = 1 : Realistic ice_shelf formulation
86      !!                        2 : Beckmann & Goose parameterization
87      !!                        3 : Specified runoff in deptht (Mathiot & al. )
88      !!                        4 : specified fwf and heat flux forcing beneath the ice shelf
89      !!----------------------------------------------------------------------
90      INTEGER, INTENT(in) ::   kt   ! ocean time step
91      !
92      INTEGER ::   ji, jj, jk   ! loop index
93      INTEGER ::   ikt, ikb     ! local integers
94      REAL(wp), DIMENSION(jpi,jpj) ::   zt_frz, zdep   ! freezing temperature (zt_frz) at depth (zdep)
95      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   zqhcisf2d
96      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   zfwfisf3d, zqhcisf3d, zqlatisf3d
97      !!---------------------------------------------------------------------
98      !
99      IF( MOD( kt-1, nn_fsbc) == 0 ) THEN    ! compute salt and heat flux
100         !
101         SELECT CASE ( nn_isf )
102         CASE ( 1 )    ! realistic ice shelf formulation
103            ! compute T/S/U/V for the top boundary layer
104            CALL sbc_isf_tbl(tsn(:,:,:,jp_tem),ttbl(:,:),'T')
105            CALL sbc_isf_tbl(tsn(:,:,:,jp_sal),stbl(:,:),'T')
106            CALL sbc_isf_tbl(un(:,:,:)        ,utbl(:,:),'U')
107            CALL sbc_isf_tbl(vn(:,:,:)        ,vtbl(:,:),'V')
108            ! iom print
109            CALL iom_put('ttbl',ttbl(:,:))
110            CALL iom_put('stbl',stbl(:,:))
111            CALL iom_put('utbl',utbl(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:))
112            CALL iom_put('vtbl',vtbl(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:))
113            ! compute fwf and heat flux
114            ! compute fwf and heat flux
115            IF( .NOT.l_isfcpl ) THEN    ;   CALL sbc_isf_cav (kt)
116            ELSE                        ;   qisf(:,:)  = fwfisf(:,:) * rlfusisf  ! heat        flux
117            ENDIF
118            !
119         CASE ( 2 )    ! Beckmann and Goosse parametrisation
120            stbl(:,:)   = soce
121            CALL sbc_isf_bg03(kt)
122            !
123         CASE ( 3 )    ! specified runoff in depth (Mathiot et al., XXXX in preparation)
124            ! specified runoff in depth (Mathiot et al., XXXX in preparation)
125            IF( .NOT.l_isfcpl ) THEN
126               CALL fld_read ( kt, nn_fsbc, sf_rnfisf   )
127               fwfisf(:,:) = - sf_rnfisf(1)%fnow(:,:,1)         ! fresh water flux from the isf (fwfisf <0 mean melting)
128            ENDIF
129            qisf(:,:)   = fwfisf(:,:) * rlfusisf             ! heat flux
130            stbl(:,:)   = soce
131            !
132         CASE ( 4 )    ! specified fwf and heat flux forcing beneath the ice shelf
133            !          ! specified fwf and heat flux forcing beneath the ice shelf
134            IF( .NOT.l_isfcpl ) THEN
135               CALL fld_read ( kt, nn_fsbc, sf_fwfisf   )
136               !CALL fld_read ( kt, nn_fsbc, sf_qisf   )
137               fwfisf(:,:) = -sf_fwfisf(1)%fnow(:,:,1)            ! fwf
138            ENDIF
139            qisf(:,:)   = fwfisf(:,:) * rlfusisf               ! heat flux
140            stbl(:,:)   = soce
141            !
142         END SELECT
143
144         ! compute tsc due to isf
145         ! isf melting implemented as a volume flux and we assume that melt water is at 0 PSU.
146         ! WARNING water add at temp = 0C, need to add a correction term (fwfisf * tfreez / rau0).
147         ! compute freezing point beneath ice shelf (or top cell if nn_isf = 3)
148         DO jj = 1,jpj
149            DO ji = 1,jpi
150               zdep(ji,jj)=gdepw_n(ji,jj,misfkt(ji,jj))
151            END DO
152         END DO
153         CALL eos_fzp( stbl(:,:), zt_frz(:,:), zdep(:,:) )
154         
155         risf_tsc(:,:,jp_tem) = qisf(:,:) * r1_rau0_rcp - fwfisf(:,:) * zt_frz(:,:) * r1_rau0 !
156         risf_tsc(:,:,jp_sal) = 0.0_wp
157
158         ! lbclnk
159         CALL lbc_lnk_multi( risf_tsc(:,:,jp_tem), 'T', 1., risf_tsc(:,:,jp_sal), 'T', 1., fwfisf,'T', 1., qisf, 'T', 1.)
160         ! output
161         IF( iom_use('iceshelf_cea') )   CALL iom_put( 'iceshelf_cea', -fwfisf(:,:)                      )   ! isf mass flux
162         IF( iom_use('hflx_isf_cea') )   CALL iom_put( 'hflx_isf_cea', risf_tsc(:,:,jp_tem) * rau0 * rcp )   ! isf sensible+latent heat (W/m2)
163         IF( iom_use('qlatisf' ) )       CALL iom_put( 'qlatisf'     , qisf(:,:)                         )   ! isf latent heat
164         IF( iom_use('fwfisf'  ) )       CALL iom_put( 'fwfisf'      , fwfisf(:,:)                       )   ! isf mass flux (opposite sign)
165
166         ! Diagnostics
167         IF( iom_use('fwfisf3d') .OR. iom_use('qlatisf3d') .OR. iom_use('qhcisf3d') .OR. iom_use('qhcisf')) THEN
168            ALLOCATE( zfwfisf3d(jpi,jpj,jpk) , zqhcisf3d(jpi,jpj,jpk) , zqlatisf3d(jpi,jpj,jpk) )
169            ALLOCATE( zqhcisf2d(jpi,jpj) )
170            !
171            zfwfisf3d (:,:,:) = 0._wp                         ! 3d ice shelf melting (kg/m2/s)
172            zqhcisf3d (:,:,:) = 0._wp                         ! 3d heat content flux (W/m2)
173            zqlatisf3d(:,:,:) = 0._wp                         ! 3d ice shelf melting latent heat flux (W/m2)
174            zqhcisf2d (:,:)   = fwfisf(:,:) * zt_frz * rcp    ! 2d heat content flux (W/m2)
175            !
176            DO jj = 1,jpj
177               DO ji = 1,jpi
178                  ikt = misfkt(ji,jj)
179                  ikb = misfkb(ji,jj)
180                  DO jk = ikt, ikb - 1
181                     zfwfisf3d (ji,jj,jk) = zfwfisf3d (ji,jj,jk) + fwfisf   (ji,jj) * r1_hisf_tbl(ji,jj) * e3t_n(ji,jj,jk)
182                     zqhcisf3d (ji,jj,jk) = zqhcisf3d (ji,jj,jk) + zqhcisf2d(ji,jj) * r1_hisf_tbl(ji,jj) * e3t_n(ji,jj,jk)
183                     zqlatisf3d(ji,jj,jk) = zqlatisf3d(ji,jj,jk) + qisf     (ji,jj) * r1_hisf_tbl(ji,jj) * e3t_n(ji,jj,jk)
184                  END DO
185                  zfwfisf3d (ji,jj,jk) = zfwfisf3d (ji,jj,jk) + fwfisf   (ji,jj) * r1_hisf_tbl(ji,jj)   & 
186                     &                                                                   * ralpha(ji,jj) * e3t_n(ji,jj,jk)
187                  zqhcisf3d (ji,jj,jk) = zqhcisf3d (ji,jj,jk) + zqhcisf2d(ji,jj) * r1_hisf_tbl(ji,jj)   & 
188                     &                                                                   * ralpha(ji,jj) * e3t_n(ji,jj,jk)
189                  zqlatisf3d(ji,jj,jk) = zqlatisf3d(ji,jj,jk) + qisf     (ji,jj) * r1_hisf_tbl(ji,jj)   & 
190                     &                                                                   * ralpha(ji,jj) * e3t_n(ji,jj,jk)
191               END DO
192            END DO
193            !
194            CALL iom_put('fwfisf3d' , zfwfisf3d (:,:,:))
195            CALL iom_put('qlatisf3d', zqlatisf3d(:,:,:))
196            CALL iom_put('qhcisf3d' , zqhcisf3d (:,:,:))
197            CALL iom_put('qhcisf'   , zqhcisf2d (:,:  ))
198            !
199            DEALLOCATE( zfwfisf3d, zqhcisf3d, zqlatisf3d )
200            DEALLOCATE( zqhcisf2d )
201         ENDIF
202         !
203      ENDIF
204
205      IF( kt == nit000 ) THEN                         !   set the forcing field at nit000 - 1    !
206         IF( ln_rstart .AND.    &                     ! Restart: read in restart file
207            &   iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN
208            IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file'
209            CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:) )   ! before salt content isf_tsc trend
210            CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal) )   ! before salt content isf_tsc trend
211            CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem) )   ! before salt content isf_tsc trend
212         ELSE
213            fwfisf_b(:,:)    = fwfisf(:,:)
214            risf_tsc_b(:,:,:)= risf_tsc(:,:,:)
215         ENDIF
216      ENDIF
217      !
218      IF( lrst_oce ) THEN
219         IF(lwp) WRITE(numout,*)
220         IF(lwp) WRITE(numout,*) 'sbc : isf surface tracer content forcing fields written in ocean restart file ',   &
221            &                    'at it= ', kt,' date= ', ndastp
222         IF(lwp) WRITE(numout,*) '~~~~'
223         CALL iom_rstput( kt, nitrst, numrow, 'fwf_isf_b', fwfisf(:,:) )
224         CALL iom_rstput( kt, nitrst, numrow, 'isf_hc_b' , risf_tsc(:,:,jp_tem) )
225         CALL iom_rstput( kt, nitrst, numrow, 'isf_sc_b' , risf_tsc(:,:,jp_sal) )
226      ENDIF
227      !
228   END SUBROUTINE sbc_isf
229
230
231   INTEGER FUNCTION sbc_isf_alloc()
232      !!----------------------------------------------------------------------
233      !!               ***  FUNCTION sbc_isf_rnf_alloc  ***
234      !!----------------------------------------------------------------------
235      sbc_isf_alloc = 0       ! set to zero if no array to be allocated
236      IF( .NOT. ALLOCATED( qisf ) ) THEN
237         ALLOCATE(  risf_tsc(jpi,jpj,jpts), risf_tsc_b(jpi,jpj,jpts), qisf(jpi,jpj)   , &
238               &    rhisf_tbl(jpi,jpj)    , r1_hisf_tbl(jpi,jpj), rzisf_tbl(jpi,jpj)  , &
239               &    ttbl(jpi,jpj)         , stbl(jpi,jpj)       , utbl(jpi,jpj)       , &
240               &    vtbl(jpi, jpj)        , risfLeff(jpi,jpj)   , rhisf_tbl_0(jpi,jpj), &
241               &    ralpha(jpi,jpj)       , misfkt(jpi,jpj)     , misfkb(jpi,jpj)     , &
242               &    STAT= sbc_isf_alloc )
243         !
244         IF( lk_mpp             )   CALL mpp_sum ( sbc_isf_alloc )
245         IF( sbc_isf_alloc /= 0 )   CALL ctl_warn('sbc_isf_alloc: failed to allocate arrays.')
246         !
247      ENDIF
248   END FUNCTION
249
250
251  SUBROUTINE sbc_isf_init
252      !!---------------------------------------------------------------------
253      !!                  ***  ROUTINE sbc_isf_init  ***
254      !!
255      !! ** Purpose : Initialisation of variables for iceshelf fluxes formulation
256      !!
257      !! ** Method  :  4 parameterizations are available according to nn_isf
258      !!               nn_isf = 1 : Realistic ice_shelf formulation
259      !!                        2 : Beckmann & Goose parameterization
260      !!                        3 : Specified runoff in deptht (Mathiot & al. )
261      !!                        4 : specified fwf and heat flux forcing beneath the ice shelf
262      !!----------------------------------------------------------------------
263      INTEGER               :: ji, jj, jk           ! loop index
264      INTEGER               :: ik                   ! current level index
265      INTEGER               :: ikt, ikb             ! top and bottom level of the isf boundary layer
266      INTEGER               :: inum, ierror
267      INTEGER               :: ios                  ! Local integer output status for namelist read
268      REAL(wp)              :: zhk
269      CHARACTER(len=256)    :: cvarzisf, cvarhisf   ! name for isf file
270      CHARACTER(LEN=32 )    :: cvarLeff             ! variable name for efficient Length scale
271      !!----------------------------------------------------------------------
272      NAMELIST/namsbc_isf/ nn_isfblk, rn_hisf_tbl, rn_gammat0, rn_gammas0, nn_gammablk, nn_isf, &
273                         & sn_fwfisf, sn_rnfisf, sn_depmax_isf, sn_depmin_isf, sn_Leff_isf
274      !!----------------------------------------------------------------------
275
276      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
277      READ  ( numnam_ref, namsbc_isf, IOSTAT = ios, ERR = 901)
278901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_isf in reference namelist', lwp )
279
280      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
281      READ  ( numnam_cfg, namsbc_isf, IOSTAT = ios, ERR = 902 )
282902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_isf in configuration namelist', lwp )
283      IF(lwm) WRITE ( numond, namsbc_isf )
284
285      IF(lwp) WRITE(numout,*)
286      IF(lwp) WRITE(numout,*) 'sbc_isf_init : heat flux of the ice shelf'
287      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
288      IF(lwp) WRITE(numout,*) '   Namelist namsbc_isf :'
289      IF(lwp) WRITE(numout,*) '      type ice shelf melting/freezing         nn_isf      = ', nn_isf
290      IF(lwp) WRITE(numout,*) '      bulk formulation (nn_isf=1 only)        nn_isfblk   = ', nn_isfblk
291      IF(lwp) WRITE(numout,*) '      thickness of the top boundary layer     rn_hisf_tbl = ', rn_hisf_tbl
292      IF(lwp) WRITE(numout,*) '      gamma formulation                       nn_gammablk = ', nn_gammablk 
293      IF(lwp) WRITE(numout,*) '      gammat coefficient                      rn_gammat0  = ', rn_gammat0 
294      IF(lwp) WRITE(numout,*) '      gammas coefficient                      rn_gammas0  = ', rn_gammas0 
295      IF(lwp) WRITE(numout,*) '      top drag coef. used (from namdrg_top)   rn_Cd0      = ', r_Cdmin_top 
296
297
298                           !  1 = presence of ISF    2 = bg03 parametrisation
299                           !  3 = rnf file for isf   4 = ISF fwf specified
300                           !  option 1 and 4 need ln_isfcav = .true. (domzgr)
301      !
302      ! Allocate public variable
303      IF ( sbc_isf_alloc()  /= 0 )         CALL ctl_stop( 'STOP', 'sbc_isf : unable to allocate arrays' )
304      !
305      ! initialisation
306      qisf    (:,:)    = 0._wp   ;   fwfisf  (:,:) = 0._wp
307      risf_tsc(:,:,:)  = 0._wp   ;   fwfisf_b(:,:) = 0._wp
308      !
309      ! define isf tbl tickness, top and bottom indice
310      SELECT CASE ( nn_isf )
311      CASE ( 1 ) 
312         IF(lwp) WRITE(numout,*)
313         IF(lwp) WRITE(numout,*) '      ==>>>   presence of under iceshelf seas (nn_isf = 1)'
314         rhisf_tbl(:,:) = rn_hisf_tbl
315         misfkt   (:,:) = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv
316         !
317      CASE ( 2 , 3 )
318         IF( .NOT.l_isfcpl ) THEN
319             ALLOCATE( sf_rnfisf(1), STAT=ierror )
320             ALLOCATE( sf_rnfisf(1)%fnow(jpi,jpj,1), sf_rnfisf(1)%fdta(jpi,jpj,1,2) )
321             CALL fld_fill( sf_rnfisf, (/ sn_rnfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' )
322          ENDIF
323          !  read effective lenght (BG03)
324          IF( nn_isf == 2 ) THEN
325            IF(lwp) WRITE(numout,*)
326            IF(lwp) WRITE(numout,*) '      ==>>>   bg03 parametrisation (nn_isf = 2)'
327            CALL iom_open( sn_Leff_isf%clname, inum )
328            cvarLeff = TRIM(sn_Leff_isf%clvar)
329            CALL iom_get( inum, jpdom_data, cvarLeff, risfLeff , 1)
330            CALL iom_close(inum)
331            !
332            risfLeff = risfLeff*1000.0_wp           !: convertion in m
333         ELSE
334            IF(lwp) WRITE(numout,*)
335            IF(lwp) WRITE(numout,*) '      ==>>>   rnf file for isf (nn_isf = 3)'
336         ENDIF
337         ! read depth of the top and bottom of the isf top boundary layer (in this case, isf front depth and grounding line depth)
338         CALL iom_open( sn_depmax_isf%clname, inum )
339         cvarhisf = TRIM(sn_depmax_isf%clvar)
340         CALL iom_get( inum, jpdom_data, cvarhisf, rhisf_tbl, 1) !: depth of deepest point of the ice shelf base
341         CALL iom_close(inum)
342         !
343         CALL iom_open( sn_depmin_isf%clname, inum )
344         cvarzisf = TRIM(sn_depmin_isf%clvar)
345         CALL iom_get( inum, jpdom_data, cvarzisf, rzisf_tbl, 1) !: depth of shallowest point of the ice shelves base
346         CALL iom_close(inum)
347         !
348         rhisf_tbl(:,:) = rhisf_tbl(:,:) - rzisf_tbl(:,:)        !: tickness isf boundary layer
349
350         !! compute first level of the top boundary layer
351         DO ji = 1, jpi
352            DO jj = 1, jpj
353                ik = 2
354!!gm potential bug: use gdepw_0 not _n
355                DO WHILE ( ik <= mbkt(ji,jj) .AND. gdepw_n(ji,jj,ik) < rzisf_tbl(ji,jj) ) ;  ik = ik + 1 ;  END DO
356                misfkt(ji,jj) = ik-1
357            END DO
358         END DO
359         !
360      CASE ( 4 ) 
361         IF(lwp) WRITE(numout,*)
362         IF(lwp) WRITE(numout,*) '      ==>>>   specified fresh water flux in ISF (nn_isf = 4)'
363         ! as in nn_isf == 1
364         rhisf_tbl(:,:) = rn_hisf_tbl
365         misfkt   (:,:) = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv
366         !
367         ! load variable used in fldread (use for temporal interpolation of isf fwf forcing)
368         IF( .NOT.l_isfcpl ) THEN
369           ALLOCATE( sf_fwfisf(1), STAT=ierror )
370           ALLOCATE( sf_fwfisf(1)%fnow(jpi,jpj,1), sf_fwfisf(1)%fdta(jpi,jpj,1,2) )
371           CALL fld_fill( sf_fwfisf, (/ sn_fwfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' )
372         ENDIF
373         !
374      CASE DEFAULT
375         CALL ctl_stop( 'sbc_isf_init: wrong value of nn_isf' )
376      END SELECT
377         
378      rhisf_tbl_0(:,:) = rhisf_tbl(:,:)
379
380      ! compute bottom level of isf tbl and thickness of tbl below the ice shelf
381      DO jj = 1,jpj
382         DO ji = 1,jpi
383            ikt = misfkt(ji,jj)
384            ikb = misfkt(ji,jj)
385            ! thickness of boundary layer at least the top level thickness
386            rhisf_tbl(ji,jj) = MAX(rhisf_tbl_0(ji,jj), e3t_n(ji,jj,ikt))
387
388            ! determine the deepest level influenced by the boundary layer
389            DO jk = ikt+1, mbkt(ji,jj)
390               IF( (SUM(e3t_n(ji,jj,ikt:jk-1)) < rhisf_tbl(ji,jj)) .AND. (tmask(ji,jj,jk) == 1) )   ikb = jk
391            END DO
392            rhisf_tbl(ji,jj) = MIN(rhisf_tbl(ji,jj), SUM(e3t_n(ji,jj,ikt:ikb))) ! limit the tbl to water thickness.
393            misfkb(ji,jj) = ikb                                                   ! last wet level of the tbl
394            r1_hisf_tbl(ji,jj) = 1._wp / rhisf_tbl(ji,jj)
395
396            zhk           = SUM( e3t_n(ji, jj, ikt:ikb - 1)) * r1_hisf_tbl(ji,jj) ! proportion of tbl cover by cell from ikt to ikb - 1
397            ralpha(ji,jj) = rhisf_tbl(ji,jj) * (1._wp - zhk ) / e3t_n(ji,jj,ikb)  ! proportion of bottom cell influenced by boundary layer
398         END DO
399      END DO
400
401  END SUBROUTINE sbc_isf_init
402
403
404  SUBROUTINE sbc_isf_bg03(kt)
405      !!---------------------------------------------------------------------
406      !!                  ***  ROUTINE sbc_isf_bg03  ***
407      !!
408      !! ** Purpose : add net heat and fresh water flux from ice shelf melting
409      !!          into the adjacent ocean
410      !!
411      !! ** Method  :   See reference
412      !!
413      !! ** Reference : Beckmann and Goosse (2003), "A parameterization of ice shelf-ocean
414      !!         interaction for climate models", Ocean Modelling 5(2003) 157-170.
415      !!         (hereafter BG)
416      !! History :  06-02  (C. Wang) Original code
417      !!----------------------------------------------------------------------
418      INTEGER, INTENT ( in ) :: kt
419      !
420      INTEGER  :: ji, jj, jk ! dummy loop index
421      INTEGER  :: ik         ! current level
422      REAL(wp) :: zt_sum     ! sum of the temperature between 200m and 600m
423      REAL(wp) :: zt_ave     ! averaged temperature between 200m and 600m
424      REAL(wp) :: zt_frz     ! freezing point temperature at depth z
425      REAL(wp) :: zpress     ! pressure to compute the freezing point in depth
426      !!----------------------------------------------------------------------
427      !
428      DO ji = 1, jpi
429         DO jj = 1, jpj
430            ik = misfkt(ji,jj)
431            !! Initialize arrays to 0 (each step)
432            zt_sum = 0.e0_wp
433            IF ( ik > 1 ) THEN
434               ! 1. -----------the average temperature between 200m and 600m ---------------------
435               DO jk = misfkt(ji,jj),misfkb(ji,jj)
436                  ! freezing point temperature  at ice shelf base BG eq. 2 (JMM sign pb ??? +7.64e-4 !!!)
437                  ! after verif with UNESCO, wrong sign in BG eq. 2
438                  ! Calculate freezing temperature
439                  CALL eos_fzp(stbl(ji,jj), zt_frz, zpress) 
440                  zt_sum = zt_sum + (tsn(ji,jj,jk,jp_tem)-zt_frz) * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)  ! sum temp
441               END DO
442               zt_ave = zt_sum/rhisf_tbl(ji,jj) ! calcul mean value
443               ! 2. ------------Net heat flux and fresh water flux due to the ice shelf
444               ! For those corresponding to zonal boundary   
445               qisf(ji,jj) = - rau0 * rcp * rn_gammat0 * risfLeff(ji,jj) * e1t(ji,jj) * zt_ave  &
446                           & * r1_e1e2t(ji,jj) * tmask(ji,jj,jk)
447             
448               fwfisf(ji,jj) = qisf(ji,jj) / rlfusisf          !fresh water flux kg/(m2s)                 
449               fwfisf(ji,jj) = fwfisf(ji,jj) * ( soce / stbl(ji,jj) )
450               !add to salinity trend
451            ELSE
452               qisf(ji,jj) = 0._wp   ;   fwfisf(ji,jj) = 0._wp
453            END IF
454         END DO
455      END DO
456      !
457  END SUBROUTINE sbc_isf_bg03
458
459
460  SUBROUTINE sbc_isf_cav( kt )
461      !!---------------------------------------------------------------------
462      !!                     ***  ROUTINE sbc_isf_cav  ***
463      !!
464      !! ** Purpose :   handle surface boundary condition under ice shelf
465      !!
466      !! ** Method  : -
467      !!
468      !! ** Action  :   utau, vtau : remain unchanged
469      !!                taum, wndm : remain unchanged
470      !!                qns        : update heat flux below ice shelf
471      !!                emp, emps  : update freshwater flux below ice shelf
472      !!---------------------------------------------------------------------
473      INTEGER, INTENT(in) ::   kt   ! ocean time step
474      !
475      INTEGER  ::   ji, jj     ! dummy loop indices
476      INTEGER  ::   nit
477      LOGICAL  ::   lit
478      REAL(wp) ::   zlamb1, zlamb2, zlamb3
479      REAL(wp) ::   zeps1,zeps2,zeps3,zeps4,zeps6,zeps7
480      REAL(wp) ::   zaqe,zbqe,zcqe,zaqer,zdis,zsfrz,zcfac
481      REAL(wp) ::   zeps = 1.e-20_wp       
482      REAL(wp) ::   zerr
483      REAL(wp), DIMENSION(jpi,jpj) ::   zfrz
484      REAL(wp), DIMENSION(jpi,jpj) ::   zgammat, zgammas 
485      REAL(wp), DIMENSION(jpi,jpj) ::   zfwflx, zhtflx, zhtflx_b
486      !!---------------------------------------------------------------------
487      !
488      ! coeficient for linearisation of potential tfreez
489      ! Crude approximation for pressure (but commonly used)
490      zlamb1 =-0.0573_wp
491      zlamb2 = 0.0832_wp
492      zlamb3 =-7.53e-08_wp * grav * rau0
493      !
494      ! initialisation
495      zgammat(:,:) = rn_gammat0 ; zgammas (:,:) = rn_gammas0
496      zhtflx (:,:) = 0.0_wp     ; zhtflx_b(:,:) = 0.0_wp   
497      zfwflx (:,:) = 0.0_wp
498
499      ! compute ice shelf melting
500      nit = 1 ; lit = .TRUE.
501      DO WHILE ( lit )    ! maybe just a constant number of iteration as in blk_core is fine
502         SELECT CASE ( nn_isfblk )
503         CASE ( 1 )   !  ISOMIP formulation (2 equations) for volume flux (Hunter et al., 2006)
504            ! Calculate freezing temperature
505            CALL eos_fzp( stbl(:,:), zfrz(:,:), risfdep(:,:) )
506
507            ! compute gammat every where (2d)
508            CALL sbc_isf_gammats(zgammat, zgammas, zhtflx, zfwflx)
509           
510            ! compute upward heat flux zhtflx and upward water flux zwflx
511            DO jj = 1, jpj
512               DO ji = 1, jpi
513                  zhtflx(ji,jj) =   zgammat(ji,jj)*rcp*rau0*(ttbl(ji,jj)-zfrz(ji,jj))
514                  zfwflx(ji,jj) = - zhtflx(ji,jj)/rlfusisf
515               END DO
516            END DO
517
518            ! Compute heat flux and upward fresh water flux
519            qisf  (:,:) = - zhtflx(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:)
520            fwfisf(:,:) =   zfwflx(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:)
521
522         CASE ( 2 )  ! ISOMIP+ formulation (3 equations) for volume flux (Asay-Davis et al., 2015)
523            ! compute gammat every where (2d)
524            CALL sbc_isf_gammats(zgammat, zgammas, zhtflx, zfwflx)
525
526            ! compute upward heat flux zhtflx and upward water flux zwflx
527            ! Resolution of a 2d equation from equation 21, 22 and 23 to find Sb (Asay-Davis et al., 2015)
528            DO jj = 1, jpj
529               DO ji = 1, jpi
530                  ! compute coeficient to solve the 2nd order equation
531                  zeps1 = rcp*rau0*zgammat(ji,jj)
532                  zeps2 = rlfusisf*rau0*zgammas(ji,jj)
533                  zeps3 = rhoisf*rcpi*rkappa/MAX(risfdep(ji,jj),zeps)
534                  zeps4 = zlamb2+zlamb3*risfdep(ji,jj)
535                  zeps6 = zeps4-ttbl(ji,jj)
536                  zeps7 = zeps4-tsurf
537                  zaqe  = zlamb1 * (zeps1 + zeps3)
538                  zaqer = 0.5_wp/MIN(zaqe,-zeps)
539                  zbqe  = zeps1*zeps6+zeps3*zeps7-zeps2
540                  zcqe  = zeps2*stbl(ji,jj)
541                  zdis  = zbqe*zbqe-4.0_wp*zaqe*zcqe               
542
543                  ! Presumably zdis can never be negative because gammas is very small compared to gammat
544                  ! compute s freeze
545                  zsfrz=(-zbqe-SQRT(zdis))*zaqer
546                  IF ( zsfrz < 0.0_wp ) zsfrz=(-zbqe+SQRT(zdis))*zaqer
547
548                  ! compute t freeze (eq. 22)
549                  zfrz(ji,jj)=zeps4+zlamb1*zsfrz
550 
551                  ! zfwflx is upward water flux
552                  ! zhtflx is upward heat flux (out of ocean)
553                  ! compute the upward water and heat flux (eq. 28 and eq. 29)
554                  zfwflx(ji,jj) = rau0 * zgammas(ji,jj) * (zsfrz-stbl(ji,jj)) / MAX(zsfrz,zeps)
555                  zhtflx(ji,jj) = zgammat(ji,jj) * rau0 * rcp * (ttbl(ji,jj) - zfrz(ji,jj) ) 
556               END DO
557            END DO
558
559            ! compute heat and water flux
560            qisf  (:,:) = - zhtflx(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:)
561            fwfisf(:,:) =   zfwflx(:,:) * (1._wp - tmask(:,:,1)) * ssmask(:,:)
562
563         END SELECT
564
565         ! define if we need to iterate (nn_gammablk 0/1 do not need iteration)
566         IF ( nn_gammablk <  2 ) THEN ; lit = .FALSE.
567         ELSE                           
568            ! check total number of iteration
569            IF (nit >= 100) THEN ; CALL ctl_stop( 'STOP', 'sbc_isf_hol99 : too many iteration ...' )
570            ELSE                 ; nit = nit + 1
571            END IF
572
573            ! compute error between 2 iterations
574            ! if needed save gammat and compute zhtflx_b for next iteration
575            zerr = MAXVAL(ABS(zhtflx-zhtflx_b))
576            IF ( zerr <= 0.01_wp ) THEN ; lit = .FALSE.
577            ELSE                        ; zhtflx_b(:,:) = zhtflx(:,:)
578            END IF
579         END IF
580      END DO
581      !
582      CALL iom_put('isfgammat', zgammat)
583      CALL iom_put('isfgammas', zgammas)
584      !
585   END SUBROUTINE sbc_isf_cav
586
587
588   SUBROUTINE sbc_isf_gammats(pgt, pgs, pqhisf, pqwisf )
589      !!----------------------------------------------------------------------
590      !! ** Purpose    : compute the coefficient echange for heat flux
591      !!
592      !! ** Method     : gamma assume constant or depends of u* and stability
593      !!
594      !! ** References : Holland and Jenkins, 1999, JPO, p1787-1800, eq 14
595      !!                Jenkins et al., 2010, JPO, p2298-2312
596      !!---------------------------------------------------------------------
597      REAL(wp), DIMENSION(:,:), INTENT(  out) ::   pgt   , pgs      !
598      REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   pqhisf, pqwisf   !
599      !
600      INTEGER  :: ji, jj                     ! loop index
601      INTEGER  :: ikt                        ! local integer
602      REAL(wp) :: zdku, zdkv                 ! U, V shear
603      REAL(wp) :: zPr, zSc, zRc              ! Prandtl, Scmidth and Richardson number
604      REAL(wp) :: zmob, zmols                ! Monin Obukov length, coriolis factor at T point
605      REAL(wp) :: zbuofdep, zhnu             ! Bouyancy length scale, sublayer tickness
606      REAL(wp) :: zhmax                      ! limitation of mol
607      REAL(wp) :: zetastar                   ! stability parameter
608      REAL(wp) :: zgmolet, zgmoles, zgturb   ! contribution of modelecular sublayer and turbulence
609      REAL(wp) :: zcoef                      ! temporary coef
610      REAL(wp) :: zdep
611      REAL(wp) :: zeps = 1.0e-20_wp   
612      REAL(wp), PARAMETER :: zxsiN = 0.052_wp   ! dimensionless constant
613      REAL(wp), PARAMETER :: znu   = 1.95e-6_wp ! kinamatic viscosity of sea water (m2.s-1)
614      REAL(wp), DIMENSION(2) :: zts, zab
615      REAL(wp), DIMENSION(jpi,jpj) :: zustar   ! U, V at T point and friction velocity
616      !!---------------------------------------------------------------------
617      !
618      SELECT CASE ( nn_gammablk )
619      CASE ( 0 ) ! gamma is constant (specified in namelist)
620         !! ISOMIP formulation (Hunter et al, 2006)
621         pgt(:,:) = rn_gammat0
622         pgs(:,:) = rn_gammas0
623
624      CASE ( 1 ) ! gamma is assume to be proportional to u*
625         !! Jenkins et al., 2010, JPO, p2298-2312
626         !! Adopted by Asay-Davis et al. (2015)
627         !! compute ustar (eq. 24)
628!!gm  NB  use pCdU here so that it will incorporate local boost of Cd0 and log layer case :
629!!         zustar(:,:) = SQRT( rCdU_top(:,:) * SQRT(utbl(:,:) * utbl(:,:) + vtbl(:,:) * vtbl(:,:) + r_ke0_top) )
630!! or better :  compute ustar in zdfdrg  and use it here as well as in TKE, GLS and Co
631!!
632!!     ===>>>>    GM  to be done this chrismas
633!!         
634!!gm end
635         zustar(:,:) = SQRT( r_Cdmin_top * (utbl(:,:) * utbl(:,:) + vtbl(:,:) * vtbl(:,:) + r_ke0_top) )
636
637         !! Compute gammats
638         pgt(:,:) = zustar(:,:) * rn_gammat0
639         pgs(:,:) = zustar(:,:) * rn_gammas0
640     
641      CASE ( 2 ) ! gamma depends of stability of boundary layer
642         !! Holland and Jenkins, 1999, JPO, p1787-1800, eq 14
643         !! as MOL depends of flux and flux depends of MOL, best will be iteration (TO DO)
644         !! compute ustar
645         zustar(:,:) = SQRT( r_Cdmin_top * (utbl(:,:) * utbl(:,:) + vtbl(:,:) * vtbl(:,:) + r_ke0_top) )
646
647         !! compute Pr and Sc number (can be improved)
648         zPr =   13.8_wp
649         zSc = 2432.0_wp
650
651         !! compute gamma mole
652         zgmolet = 12.5_wp * zPr ** (2.0/3.0) - 6.0_wp
653         zgmoles = 12.5_wp * zSc ** (2.0/3.0) - 6.0_wp
654
655         !! compute gamma
656         DO ji = 2, jpi
657            DO jj = 2, jpj
658               ikt = mikt(ji,jj)
659
660               IF( zustar(ji,jj) == 0._wp ) THEN           ! only for kt = 1 I think
661                  pgt = rn_gammat0
662                  pgs = rn_gammas0
663               ELSE
664                  !! compute Rc number (as done in zdfric.F90)
665!!gm better to do it like in the new zdfric.F90   i.e. avm weighted Ri computation
666!!gm moreover, use Max(rn2,0) to take care of static instabilities....
667                  zcoef = 0.5_wp / e3w_n(ji,jj,ikt)
668                  !                                            ! shear of horizontal velocity
669                  zdku = zcoef * (  un(ji-1,jj  ,ikt  ) + un(ji,jj,ikt  )  &
670                     &             -un(ji-1,jj  ,ikt+1) - un(ji,jj,ikt+1)  )
671                  zdkv = zcoef * (  vn(ji  ,jj-1,ikt  ) + vn(ji,jj,ikt  )  &
672                     &             -vn(ji  ,jj-1,ikt+1) - vn(ji,jj,ikt+1)  )
673                  !                                            ! richardson number (minimum value set to zero)
674                  zRc = rn2(ji,jj,ikt+1) / MAX( zdku*zdku + zdkv*zdkv, zeps )
675
676                  !! compute bouyancy
677                  zts(jp_tem) = ttbl(ji,jj)
678                  zts(jp_sal) = stbl(ji,jj)
679                  zdep        = gdepw_n(ji,jj,ikt)
680                  !
681                  CALL eos_rab( zts, zdep, zab )
682                  !
683                  !! compute length scale
684                  zbuofdep = grav * ( zab(jp_tem) * pqhisf(ji,jj) - zab(jp_sal) * pqwisf(ji,jj) )  !!!!!!!!!!!!!!!!!!!!!!!!!!!!
685
686                  !! compute Monin Obukov Length
687                  ! Maximum boundary layer depth
688                  zhmax = gdept_n(ji,jj,mbkt(ji,jj)) - gdepw_n(ji,jj,mikt(ji,jj)) -0.001_wp
689                  ! Compute Monin obukhov length scale at the surface and Ekman depth:
690                  zmob   = zustar(ji,jj) ** 3 / (vkarmn * (zbuofdep + zeps))
691                  zmols  = SIGN(1._wp, zmob) * MIN(ABS(zmob), zhmax) * tmask(ji,jj,ikt)
692
693                  !! compute eta* (stability parameter)
694                  zetastar = 1._wp / ( SQRT(1._wp + MAX(zxsiN * zustar(ji,jj) / ( ABS(ff_f(ji,jj)) * zmols * zRc ), 0._wp)))
695
696                  !! compute the sublayer thickness
697                  zhnu = 5 * znu / zustar(ji,jj)
698
699                  !! compute gamma turb
700                  zgturb = 1._wp / vkarmn * LOG(zustar(ji,jj) * zxsiN * zetastar * zetastar / ( ABS(ff_f(ji,jj)) * zhnu )) &
701                  &      + 1._wp / ( 2 * zxsiN * zetastar ) - 1._wp / vkarmn
702
703                  !! compute gammats
704                  pgt(ji,jj) = zustar(ji,jj) / (zgturb + zgmolet)
705                  pgs(ji,jj) = zustar(ji,jj) / (zgturb + zgmoles)
706               END IF
707            END DO
708         END DO
709         CALL lbc_lnk_multi( pgt, 'T', 1., pgs, 'T', 1.)
710      END SELECT
711      !
712   END SUBROUTINE sbc_isf_gammats
713
714
715   SUBROUTINE sbc_isf_tbl( pvarin, pvarout, cd_ptin )
716      !!----------------------------------------------------------------------
717      !!                  ***  SUBROUTINE sbc_isf_tbl  ***
718      !!
719      !! ** Purpose : compute mean T/S/U/V in the boundary layer at T- point
720      !!
721      !!----------------------------------------------------------------------
722      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) :: pvarin
723      REAL(wp), DIMENSION(:,:)  , INTENT(  out) :: pvarout
724      CHARACTER(len=1),           INTENT(in   ) :: cd_ptin ! point of variable in/out
725      !
726      INTEGER ::   ji, jj, jk                ! loop index
727      INTEGER ::   ikt, ikb                    ! top and bottom index of the tbl
728      REAL(wp) ::   ze3, zhk
729      REAL(wp), DIMENSION(jpi,jpj) :: zhisf_tbl ! thickness of the tbl
730      !!----------------------------------------------------------------------
731     
732      ! initialisation
733      pvarout(:,:)=0._wp
734   
735      SELECT CASE ( cd_ptin )
736      CASE ( 'U' ) ! compute U in the top boundary layer at T- point
737         DO jj = 1,jpj
738            DO ji = 1,jpi
739               ikt = miku(ji,jj) ; ikb = miku(ji,jj)
740               ! thickness of boundary layer at least the top level thickness
741               zhisf_tbl(ji,jj) = MAX( rhisf_tbl_0(ji,jj) , e3u_n(ji,jj,ikt) )
742
743               ! determine the deepest level influenced by the boundary layer
744               DO jk = ikt+1, mbku(ji,jj)
745                  IF ( (SUM(e3u_n(ji,jj,ikt:jk-1)) < zhisf_tbl(ji,jj)) .AND. (umask(ji,jj,jk) == 1) ) ikb = jk
746               END DO
747               zhisf_tbl(ji,jj) = MIN(zhisf_tbl(ji,jj), SUM(e3u_n(ji,jj,ikt:ikb)))  ! limit the tbl to water thickness.
748
749               ! level fully include in the ice shelf boundary layer
750               DO jk = ikt, ikb - 1
751                  ze3 = e3u_n(ji,jj,jk)
752                  pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,jk) / zhisf_tbl(ji,jj) * ze3
753               END DO
754
755               ! level partially include in ice shelf boundary layer
756               zhk = SUM( e3u_n(ji, jj, ikt:ikb - 1)) / zhisf_tbl(ji,jj)
757               pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,ikb) * (1._wp - zhk)
758            END DO
759         END DO
760         DO jj = 2, jpj
761            DO ji = 2, jpi
762!!gm a wet-point only average should be used here !!!
763               pvarout(ji,jj) = 0.5_wp * (pvarout(ji,jj) + pvarout(ji-1,jj))
764            END DO
765         END DO
766         CALL lbc_lnk(pvarout,'T',-1.)
767     
768      CASE ( 'V' ) ! compute V in the top boundary layer at T- point
769         DO jj = 1,jpj
770            DO ji = 1,jpi
771               ikt = mikv(ji,jj) ; ikb = mikv(ji,jj)
772               ! thickness of boundary layer at least the top level thickness
773               zhisf_tbl(ji,jj) = MAX(rhisf_tbl_0(ji,jj), e3v_n(ji,jj,ikt))
774
775               ! determine the deepest level influenced by the boundary layer
776               DO jk = ikt+1, mbkv(ji,jj)
777                  IF ( (SUM(e3v_n(ji,jj,ikt:jk-1)) < zhisf_tbl(ji,jj)) .AND. (vmask(ji,jj,jk) == 1) ) ikb = jk
778               END DO
779               zhisf_tbl(ji,jj) = MIN(zhisf_tbl(ji,jj), SUM(e3v_n(ji,jj,ikt:ikb)))  ! limit the tbl to water thickness.
780
781               ! level fully include in the ice shelf boundary layer
782               DO jk = ikt, ikb - 1
783                  ze3 = e3v_n(ji,jj,jk)
784                  pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,jk) / zhisf_tbl(ji,jj) * ze3
785               END DO
786
787               ! level partially include in ice shelf boundary layer
788               zhk = SUM( e3v_n(ji, jj, ikt:ikb - 1)) / zhisf_tbl(ji,jj)
789               pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,ikb) * (1._wp - zhk)
790            END DO
791         END DO
792         DO jj = 2, jpj
793            DO ji = 2, jpi
794!!gm a wet-point only average should be used here !!!
795               pvarout(ji,jj) = 0.5_wp * (pvarout(ji,jj) + pvarout(ji,jj-1))
796            END DO
797         END DO
798         CALL lbc_lnk(pvarout,'T',-1.)
799
800      CASE ( 'T' ) ! compute T in the top boundary layer at T- point
801         DO jj = 1,jpj
802            DO ji = 1,jpi
803               ikt = misfkt(ji,jj)
804               ikb = misfkb(ji,jj)
805
806               ! level fully include in the ice shelf boundary layer
807               DO jk = ikt, ikb - 1
808                  ze3 = e3t_n(ji,jj,jk)
809                  pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,jk) * r1_hisf_tbl(ji,jj) * ze3
810               END DO
811
812               ! level partially include in ice shelf boundary layer
813               zhk = SUM( e3t_n(ji, jj, ikt:ikb - 1)) * r1_hisf_tbl(ji,jj)
814               pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,ikb) * (1._wp - zhk)
815            END DO
816         END DO
817      END SELECT
818      !
819      ! mask mean tbl value
820      pvarout(:,:) = pvarout(:,:) * ssmask(:,:)
821      !
822   END SUBROUTINE sbc_isf_tbl
823     
824
825   SUBROUTINE sbc_isf_div( phdivn )
826      !!----------------------------------------------------------------------
827      !!                  ***  SUBROUTINE sbc_isf_div  ***
828      !!       
829      !! ** Purpose :   update the horizontal divergence with the runoff inflow
830      !!
831      !! ** Method  :   
832      !!                CAUTION : risf_tsc(:,:,jp_sal) is negative (outflow) increase the
833      !!                          divergence and expressed in m/s
834      !!
835      !! ** Action  :   phdivn   decreased by the runoff inflow
836      !!----------------------------------------------------------------------
837      REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   phdivn   ! horizontal divergence
838      !
839      INTEGER  ::   ji, jj, jk   ! dummy loop indices
840      INTEGER  ::   ikt, ikb 
841      REAL(wp) ::   zhk
842      REAL(wp) ::   zfact     ! local scalar
843      !!----------------------------------------------------------------------
844      !
845      zfact   = 0.5_wp
846      !
847      IF(.NOT.ln_linssh ) THEN     ! need to re compute level distribution of isf fresh water
848         DO jj = 1,jpj
849            DO ji = 1,jpi
850               ikt = misfkt(ji,jj)
851               ikb = misfkt(ji,jj)
852               ! thickness of boundary layer at least the top level thickness
853               rhisf_tbl(ji,jj) = MAX(rhisf_tbl_0(ji,jj), e3t_n(ji,jj,ikt))
854
855               ! determine the deepest level influenced by the boundary layer
856               DO jk = ikt, mbkt(ji,jj)
857                  IF ( (SUM(e3t_n(ji,jj,ikt:jk-1)) .LT. rhisf_tbl(ji,jj)) .AND. (tmask(ji,jj,jk) == 1) ) ikb = jk
858               END DO
859               rhisf_tbl(ji,jj) = MIN(rhisf_tbl(ji,jj), SUM(e3t_n(ji,jj,ikt:ikb)))  ! limit the tbl to water thickness.
860               misfkb(ji,jj) = ikb                                                  ! last wet level of the tbl
861               r1_hisf_tbl(ji,jj) = 1._wp / rhisf_tbl(ji,jj)
862
863               zhk           = SUM( e3t_n(ji, jj, ikt:ikb - 1)) * r1_hisf_tbl(ji,jj)  ! proportion of tbl cover by cell from ikt to ikb - 1
864               ralpha(ji,jj) = rhisf_tbl(ji,jj) * (1._wp - zhk ) / e3t_n(ji,jj,ikb)  ! proportion of bottom cell influenced by boundary layer
865            END DO
866         END DO
867      END IF 
868      !
869      !==   ice shelf melting distributed over several levels   ==!
870      DO jj = 1,jpj
871         DO ji = 1,jpi
872               ikt = misfkt(ji,jj)
873               ikb = misfkb(ji,jj)
874               ! level fully include in the ice shelf boundary layer
875               DO jk = ikt, ikb - 1
876                  phdivn(ji,jj,jk) = phdivn(ji,jj,jk) + ( fwfisf(ji,jj) + fwfisf_b(ji,jj) ) &
877                    &              * r1_hisf_tbl(ji,jj) * r1_rau0 * zfact
878               END DO
879               ! level partially include in ice shelf boundary layer
880               phdivn(ji,jj,ikb) = phdivn(ji,jj,ikb) + ( fwfisf(ji,jj) &
881                    &            + fwfisf_b(ji,jj) ) * r1_hisf_tbl(ji,jj) * r1_rau0 * zfact * ralpha(ji,jj) 
882         END DO
883      END DO
884      !
885   END SUBROUTINE sbc_isf_div
886
887   !!======================================================================
888END MODULE sbcisf
Note: See TracBrowser for help on using the repository browser.