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/UKMO/dev_r6501_GO6_package_trunk/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r6501_GO6_package_trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcisf.F90 @ 6825

Last change on this file since 6825 was 6825, checked in by timgraham, 8 years ago

As used for GO6 from trunk test

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