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.
isfstp.F90 in NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfstp.F90 @ 11489

Last change on this file since 11489 was 11489, checked in by mathiot, 5 years ago

ENHANCE-02_ISF: move ln_isf out of namsbc and add an easy way to run with isf cavity and no ice shelf melt (ticket #2142)

  • Property svn:keywords set to Id
File size: 14.3 KB
Line 
1MODULE isfstp
2   !!======================================================================
3   !!                       ***  MODULE  isfstp  ***
4   !! Surface module :  compute iceshelf load, melt and heat flux
5   !!======================================================================
6   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
7   !!            X.X  !  2006-02  (C. Wang   ) Original code bg03
8   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
9   !!            4.1  !  2019-09  (P. Mathiot) Split param/explicit ice shelf and re-organisation
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   isfstp       : compute iceshelf melt and heat flux
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   USE isfrst         ! iceshelf restart
29   USE isftbl         ! ice shelf boundary layer
30   USE isfpar         ! ice shelf parametrisation
31   USE isfcav         ! ice shelf cavity
32   USE isfload        ! ice shelf load
33   USE isfcpl         ! isf variables
34   USE isf            ! isf variables
35
36   IMPLICIT NONE
37
38   PRIVATE
39
40   PUBLIC   isf_stp, isf_stp_init  ! routine called in sbcmod and divhor
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48 
49  SUBROUTINE isf_stp( kt )
50      !!---------------------------------------------------------------------
51      !!                  ***  ROUTINE isf_stp  ***
52      !!
53      !! ** Purpose : compute total heat flux and total fwf due to ice shelf melt
54      !!
55      !! ** Method  : For each case (parametrisation or explicity cavity) :
56      !!              - define the before fields
57      !!              - compute top boundary layer properties
58      !!                (in case of parametrisation, this is the
59      !!                 depth range model array used to compute mean far fields properties)
60      !!              - compute fluxes
61      !!              - write restart variables
62      !!
63      !!----------------------------------------------------------------------
64      INTEGER, INTENT(in) ::   kt   ! ocean time step
65      !!---------------------------------------------------------------------
66      !
67      IF ( ln_isfcav_mlt ) THEN
68         !
69         ! before time step
70         IF ( kt /= nit000 ) THEN
71            risf_cav_tsc_b (:,:,:) = risf_cav_tsc (:,:,:)
72            fwfisf_cav_b(:,:)      = fwfisf_cav(:,:)
73         END IF
74         !
75         ! compute tbl lvl/h
76         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav)
77         !
78         ! compute ice shelf melt
79         CALL isf_cav( kt, risf_cav_tsc, fwfisf_cav)
80         !
81         ! write restart variables (risf_cav_tsc, fwfisf for now and before)
82         IF (lrst_oce) CALL isfrst_write(kt, 'cav', risf_cav_tsc, fwfisf_cav)
83         !
84      END IF
85      !
86      IF ( ln_isfpar_mlt ) THEN
87         !
88         ! before time step
89         IF ( kt /= nit000 ) THEN
90            risf_par_tsc_b(:,:,:) = risf_par_tsc(:,:,:)
91            fwfisf_par_b  (:,:)   = fwfisf_par  (:,:)
92         END IF
93         !
94         ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl)
95         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par)
96         !
97         ! compute ice shelf melt
98         CALL isf_par( kt, risf_par_tsc, fwfisf_par)
99         !
100         ! write restart variables (qoceisf, qhcisf, fwfisf for now and before)
101         IF (lrst_oce) CALL isfrst_write(kt, 'par', risf_par_tsc, fwfisf_par)
102         !
103      END IF
104
105      IF ( ln_isfcpl ) THEN
106         IF (lrst_oce) CALL isfcpl_rst_write(kt)
107      END IF
108      !
109   END SUBROUTINE isf_stp
110
111   SUBROUTINE isf_stp_init
112      !!---------------------------------------------------------------------
113      !!                  ***  ROUTINE isfstp_init  ***
114      !!
115      !! ** Purpose :   Initialisation of the ice shelf public variables
116      !!
117      !! ** Method  :   Read the namsbc namelist and set derived parameters
118      !!                Call init routines for all other SBC modules that have one
119      !!
120      !! ** Action  : - read namsbc parameters
121      !!              - allocate memory
122      !!              - call cav/param init routine
123      !!----------------------------------------------------------------------
124      INTEGER               :: inum, ierror
125      INTEGER               :: ios                  ! Local integer output status for namelist read
126      INTEGER               :: ikt, ikb
127      INTEGER               :: ji, jj
128      !!----------------------------------------------------------------------
129      NAMELIST/namisf/ ln_isf       ,                                                                               & 
130         &             ln_isfcav_mlt, cn_isfcav_mlt, cn_gammablk, rn_gammat0, rn_gammas0, rn_htbl, sn_isfcav_fwf,   &
131         &             ln_isfpar_mlt, cn_isfpar_mlt, sn_isfpar_fwf, sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff, &
132         &             ln_isfcpl    , nn_drown, ln_isfcpl_cons,                                                     &
133         &             cn_isfload   , cn_isfdir
134      !!----------------------------------------------------------------------
135      !
136      ! Allocate public array
137      CALL isf_alloc()
138      !
139      riceload(:,:)       = 0.0_wp
140      fwfisf_oasis(:,:)   = 0.0_wp
141      fwfisf_par(:,:)     = 0.0_wp    ; fwfisf_par_b(:,:)     = 0.0_wp
142      fwfisf_cav(:,:)     = 0.0_wp    ; fwfisf_cav_b(:,:)     = 0.0_wp
143      risf_cav_tsc(:,:,:) = 0.0_wp    ; risf_cav_tsc_b(:,:,:) = 0.0_wp
144      risf_par_tsc(:,:,:) = 0.0_wp    ; risf_par_tsc_b(:,:,:) = 0.0_wp
145      !
146      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
147      READ  ( numnam_ref, namisf, IOSTAT = ios, ERR = 901)
148901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namisf in reference namelist', lwp )
149      !
150      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
151      READ  ( numnam_cfg, namisf, IOSTAT = ios, ERR = 902 )
152902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namisf in configuration namelist', lwp )
153      IF(lwm) WRITE ( numond, namisf )
154      !
155      IF (lwp) THEN
156         WRITE(numout,*)
157         WRITE(numout,*) 'isf_init : ice shelf initialisation'
158         WRITE(numout,*) '~~~~~~~~~~~~'
159         WRITE(numout,*) '   Namelist namisf :'
160         !
161         WRITE(numout,*) '   ice shelf cavity (open or parametrised)  ln_isf = ', ln_isf
162         !
163         IF ( ln_isf ) THEN
164            WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt
165            IF ( ln_isfcav ) THEN
166               WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', TRIM(cn_isfcav_mlt)
167               WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl
168               WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', TRIM(cn_gammablk) 
169               IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN
170                  WRITE(numout,*) '            gammat coefficient                      rn_gammat0  = ', rn_gammat0 
171                  WRITE(numout,*) '            gammas coefficient                      rn_gammas0  = ', rn_gammas0 
172                  WRITE(numout,*) '            top drag coef. used (from namdrg_top)   rn_Cd0      = ', r_Cdmin_top 
173               END IF
174            END IF
175            WRITE(numout,*) ''
176            !
177            WRITE(numout,*) '      ice shelf melt parametrisation          ln_isfpar_mlt    = ', ln_isfpar_mlt
178            IF ( ln_isfpar_mlt ) THEN
179               WRITE(numout,*) '         isf parametrisation formulation         cn_isfpar_mlt   = ', TRIM(cn_isfpar_mlt)
180            END IF
181            WRITE(numout,*) ''
182            !
183            WRITE(numout,*) '      Coupling to an ice sheet model          ln_isfcpl         = ', ln_isfcpl
184            IF ( ln_isfcpl ) THEN
185               WRITE(numout,*) '         conservation activated ln_isfcpl_cons           = ', ln_isfcpl_cons
186               WRITE(numout,*) '            number of call of the extrapolation loop = ', nn_drown
187            ENDIF
188            !
189            WRITE(numout,*) '      Ice shelf load method                   cn_isfload        = ', TRIM(cn_isfload)
190         ELSE
191            IF ( ln_isfcav ) THEN
192               WRITE(numout,*) ''
193               WRITE(numout,*) '   W A R N I N G: ice shelf cavities are open BUT no melt will be computed or read from file !'
194               WRITE(numout,*) ''
195            END IF
196         END IF
197
198      END IF
199      !
200      !---------------------------------------------------------------------------------------------------------------------
201      ! initialisation ice shelf load
202      IF ( ln_isfcav ) THEN
203         !
204         ! compute ice shelf mask
205         mskisf_cav(:,:) = (1._wp - tmask(:,:,1)) * ssmask(:,:)
206         !
207         ! compute ice shelf load
208         CALL isf_load( risfload )
209         !
210      END IF
211      !
212      !---------------------------------------------------------------------------------------------------------------------
213      ! sanity check
214      ! melt in the cavity without cavity
215      IF ( ln_isfcav_mlt .AND. (.NOT. ln_isfcav) ) &
216         &   CALL ctl_stop('ice shelf melt in the cavity activated (ln_isfcav_mlt) but no cavity detected in domcfg (ln_isfcav), STOP' )
217      !
218      ! ice sheet coupling without cavity
219      IF ( ln_isfcpl .AND. (.NOT. ln_isfcav) ) &
220         &   CALL ctl_stop('coupling with an ice sheet model detected (ln_isfcpl) but no cavity detected in domcfg (ln_isfcav), STOP' )
221      !
222      IF ( ln_isfcpl .AND. ln_isfcpl_cons .AND. ln_linssh ) &
223         &   CALL ctl_stop( 'The coupling between NEMO and an ice sheet model with the conservation option does not work with the linssh option' )
224      !
225      IF ( l_isfoasis ) THEN
226         !
227         CALL ctl_stop( ' ln_ctl and ice shelf not tested' )
228         !
229         ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation
230         IF ( ln_isfcav_mlt .AND. TRIM(cn_isfcav_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis is the only option availble if fwf send by oasis' )
231         IF ( ln_isfpar_mlt .AND. TRIM(cn_isfpar_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis is the only option availble if fwf send by oasis' )
232         !
233         ! oasis melt computation not tested (coded but not tested)
234         IF ( ln_isfcav_mlt .OR. ln_isfpar_mlt ) THEN
235            IF ( TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis not tested' )
236            IF ( TRIM(cn_isfpar_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis not tested' )
237         END IF
238         !
239         ! oasis melt computation with cavity open and cavity parametrised (not coded)
240         IF ( ln_isfcav_mlt .AND. ln_isfpar_mlt ) THEN
241            IF ( TRIM(cn_isfpar_mlt) == 'oasis' .AND. TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis and cn_isfcav_mlt = oasis not coded' )
242         END IF
243      END IF
244      !
245      ! terminate routine now if no ice shelf melt formulation specify
246      IF ( .NOT. ln_isf ) RETURN
247      !
248      ! initialisation useful variable
249      r1_Lfusisf =  1._wp / rLfusisf
250      !
251      ll_isfcpl     = .FALSE.
252      ll_isfcpl_cons= .FALSE.
253      !
254      ! initialisation melt in the cavity
255      IF ( ln_isfcav_mlt ) THEN
256         !
257         ! initialisation  of cav variable
258         CALL isf_cav_init()
259         !
260         ! read cav variable from restart
261         IF ( ln_rstart ) CALL isfrst_read('cav', risf_cav_tsc, fwfisf_cav, risf_cav_tsc_b, fwfisf_cav_b)
262         !
263      END IF
264      !
265      !---------------------------------------------------------------------------------------------------------------------
266      ! initialisation parametrised melt
267      IF ( ln_isfpar_mlt ) THEN
268         !
269         ! initialisation  of par variable
270         CALL isf_par_init()
271         !
272         ! read par variable from restart
273         IF ( ln_rstart ) CALL isfrst_read('par', risf_par_tsc, fwfisf_par, risf_par_tsc_b, fwfisf_par_b)
274         !
275      END IF
276      !
277      !---------------------------------------------------------------------------------------------------------------------
278      ! initialisation ice sheet coupling
279      IF( ln_isfcpl ) THEN
280
281         ! prepare writing restart
282         IF( lwxios ) CALL iom_set_rstw_var_active('ssmask')
283         IF( lwxios ) CALL iom_set_rstw_var_active('tmask')
284         !IF( lwxios ) CALL iom_set_rstw_var_active('wmask')
285         !IF( lwxios ) CALL iom_set_rstw_var_active('gdepw_n')
286         IF( lwxios ) CALL iom_set_rstw_var_active('e3t_n')
287         IF( lwxios ) CALL iom_set_rstw_var_active('e3u_n')
288         IF( lwxios ) CALL iom_set_rstw_var_active('e3v_n')
289
290         IF( ln_rstart ) THEN
291            !
292            ll_isfcpl = .TRUE.
293            !
294            CALL isf_alloc_cpl()
295            !
296            ! extrapolation tracer properties
297            CALL isfcpl_tra()
298            !
299            ! correction of the horizontal divergence and associated temp. and salt content flux
300            CALL isfcpl_vol()
301            !
302            ! apply the 'conservation' method
303            IF ( ln_isfcpl_cons )  THEN
304               ll_isfcpl_cons = .TRUE.
305               CALL isfcpl_cons()
306            END IF
307            !
308            ! Need to include in the cpl cons the isfrst_cpl_div contribution
309            ! decide how to manage thickness level change in conservation
310            !
311            tsb    (:,:,:,:) = tsn (:,:,:,:)
312            sshb   (:,:)     = sshn(:,:)
313            !
314         END IF
315      END IF
316         
317  END SUBROUTINE isf_stp_init
318   !!======================================================================
319END MODULE isfstp
Note: See TracBrowser for help on using the repository browser.