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

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

ENHANCE-02_ISF: fix coupling issue (ticket #2142)

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