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/tests/ISOMIP+/MY_SRC – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/tests/ISOMIP+/MY_SRC/isfstp.F90 @ 11931

Last change on this file since 11931 was 11931, checked in by mathiot, 4 years ago

ENHANCE-02_ISF_nemo: add comments, improve memory usage of ln_isfcpl_cons option, fix issue in ISOMIP+ configuration

File size: 13.7 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   !
16   USE isf            ! isf variables
17   USE isfload, ONLY: isf_load                      ! ice shelf load
18   USE isftbl , ONLY: isf_tbl_lvl                   ! ice shelf boundary layer
19   USE isfpar , ONLY: isf_par, isf_par_init         ! ice shelf parametrisation
20   USE isfcav , ONLY: isf_cav, isf_cav_init         ! ice shelf cavity
21   USE isfcpl , ONLY: isfcpl_rst_write, isfcpl_init ! isf variables
22
23   USE dom_oce, ONLY: ht_n, e3t_n, ln_isfcav, ln_linssh ! ocean space and time domain
24   USE domvvl,  ONLY: ln_vvl_zstar                      ! zstar logical
25   USE zdfdrg,  ONLY: r_Cdmin_top, r_ke0_top            ! vertical physics: top/bottom drag coef.
26   !
27   USE lib_mpp, ONLY: ctl_stop, ctl_nam
28   USE in_out_manager ! I/O manager
29   USE timing
30
31   IMPLICIT NONE
32
33   PRIVATE
34
35   PUBLIC   isf_stp, isf_init, isf_nam  ! routine called in sbcmod and divhor
36
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id: isfstp.F90 11876 2019-11-08 11:26:42Z mathiot $
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43 
44  SUBROUTINE isf_stp( kt )
45      !!---------------------------------------------------------------------
46      !!                  ***  ROUTINE isf_stp  ***
47      !!
48      !! ** Purpose : compute total heat flux and total fwf due to ice shelf melt
49      !!
50      !! ** Method  : For each case (parametrisation or explicity cavity) :
51      !!              - define the before fields
52      !!              - compute top boundary layer properties
53      !!                (in case of parametrisation, this is the
54      !!                 depth range model array used to compute mean far fields properties)
55      !!              - compute fluxes
56      !!              - write restart variables
57      !!
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(in) ::   kt   ! ocean time step
60      !!---------------------------------------------------------------------
61      !
62      IF( ln_timing )   CALL timing_start('isf')
63      !
64      IF ( ln_isfcav_mlt ) THEN
65         !
66         ! before time step
67         IF ( kt /= nit000 ) THEN
68            risf_cav_tsc_b (:,:,:) = risf_cav_tsc (:,:,:)
69            fwfisf_cav_b(:,:)      = fwfisf_cav(:,:)
70         END IF
71         !
72         ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl)
73         rhisf_tbl_cav(:,:) = rn_htbl * mskisf_cav(:,:)
74         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav)
75         !
76         ! compute ice shelf melt
77         CALL isf_cav( kt, risf_cav_tsc, fwfisf_cav)
78         !
79      END IF
80      !
81      IF ( ln_isfpar_mlt ) THEN
82         !
83         ! before time step
84         IF ( kt /= nit000 ) THEN
85            risf_par_tsc_b(:,:,:) = risf_par_tsc(:,:,:)
86            fwfisf_par_b  (:,:)   = fwfisf_par  (:,:)
87         END IF
88         !
89         ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl)
90         ! by simplicity, we assume the top level where param applied do not change with time
91         rhisf_tbl_par(:,:) = rhisf0_tbl_par(:,:)
92         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par)
93         !
94         ! compute ice shelf melt
95         CALL isf_par( kt, risf_par_tsc, fwfisf_par)
96         !
97      END IF
98      !
99      IF ( ln_isfcpl ) THEN
100         ! after step nit000 + 2 we do not need anymore the risfcpl_ arrays
101         IF ( kt == nit000 + 2 ) CALL isf_dealloc_cpl()
102
103         IF ( lrst_oce ) CALL isfcpl_rst_write(kt)
104      END IF
105      !
106      IF( ln_timing )   CALL timing_stop('isf')
107      !
108   END SUBROUTINE isf_stp
109
110   SUBROUTINE isf_init
111      !!---------------------------------------------------------------------
112      !!                  ***  ROUTINE isfstp_init  ***
113      !!
114      !! ** Purpose :   Initialisation of the ice shelf public variables
115      !!
116      !! ** Method  :   Read the namisf namelist, check option compatibility and set derived parameters
117      !!
118      !! ** Action  : - read namisf parameters
119      !!              - allocate memory
120      !!              - output print
121      !!              - ckeck option compatibility
122      !!              - call cav/param/isfcpl init routine
123      !!----------------------------------------------------------------------
124      !
125      ! constrain: l_isfoasis need to be known
126      !
127      ! Read namelist
128      CALL isf_nam()
129      !
130      ! Allocate public array
131      CALL isf_alloc()
132      !
133      ! check option compatibility
134      CALL isf_ctl()
135      !
136      ! compute ice shelf load
137      IF ( ln_isfcav ) CALL isf_load( risfload )
138      !
139      ! terminate routine now if no ice shelf melt formulation specify
140      IF ( ln_isf ) THEN
141         !
142         !---------------------------------------------------------------------------------------------------------------------
143         ! initialisation melt in the cavity
144         IF ( ln_isfcav_mlt ) CALL isf_cav_init()
145         !
146         !---------------------------------------------------------------------------------------------------------------------
147         ! initialisation parametrised melt
148         IF ( ln_isfpar_mlt ) CALL isf_par_init()
149         !
150         !---------------------------------------------------------------------------------------------------------------------
151         ! initialisation ice sheet coupling
152         IF ( ln_isfcpl ) CALL isfcpl_init()
153         !
154      END IF
155         
156  END SUBROUTINE isf_init
157
158  SUBROUTINE isf_ctl()
159      !!---------------------------------------------------------------------
160      !!                  ***  ROUTINE isf_ctl  ***
161      !!
162      !! ** Purpose :   output print and option compatibility check
163      !!
164      !!----------------------------------------------------------------------
165      IF (lwp) THEN
166         WRITE(numout,*)
167         WRITE(numout,*) 'isf_init : ice shelf initialisation'
168         WRITE(numout,*) '~~~~~~~~~~~~'
169         WRITE(numout,*) '   Namelist namisf :'
170         !
171         WRITE(numout,*) '   ice shelf cavity (open or parametrised)  ln_isf = ', ln_isf
172         WRITE(numout,*)
173         !
174         IF ( ln_isf ) THEN
175            WRITE(numout,*) '      Add debug print in isf module           ln_isfdebug     = ', ln_isfdebug
176            WRITE(numout,*)
177            WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt
178            IF ( ln_isfcav_mlt) THEN
179               WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', TRIM(cn_isfcav_mlt)
180               WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl
181               WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', TRIM(cn_gammablk) 
182               IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN
183                  WRITE(numout,*) '         gammat coefficient                       rn_gammat0  = ', rn_gammat0 
184                  WRITE(numout,*) '         gammas coefficient                       rn_gammas0  = ', rn_gammas0 
185                  WRITE(numout,*) '         top background ke used (from namdrg_top) rn_vtide**2 = ', rn_vtide**2
186                  WRITE(numout,*) '         top drag coef.    used (from namdrg_top) rn_Cd0      = ', r_Cdmin_top
187               END IF
188            END IF
189            WRITE(numout,*) ''
190            !
191            WRITE(numout,*) '      ice shelf melt parametrisation          ln_isfpar_mlt   = ', ln_isfpar_mlt
192            IF ( ln_isfpar_mlt ) THEN
193               WRITE(numout,*) '         isf parametrisation formulation         cn_isfpar_mlt   = ', TRIM(cn_isfpar_mlt)
194            END IF
195            WRITE(numout,*) ''
196            !
197            WRITE(numout,*) '      Coupling to an ice sheet model          ln_isfcpl       = ', ln_isfcpl
198            IF ( ln_isfcpl ) THEN
199               WRITE(numout,*) '         conservation activated ln_isfcpl_cons     = ', ln_isfcpl_cons
200               WRITE(numout,*) '         number of call of the extrapolation loop  = ', nn_drown
201            ENDIF
202            WRITE(numout,*) ''
203            !
204         ELSE
205            !
206            IF ( ln_isfcav ) THEN
207               WRITE(numout,*) ''
208               WRITE(numout,*) '   W A R N I N G: ice shelf cavities are open BUT no melt will be computed or read from file !'
209               WRITE(numout,*) ''
210            END IF
211            !
212         END IF
213
214         IF (ln_isfcav) WRITE(numout,*) '      Ice shelf load method                   cn_isfload        = ', TRIM(cn_isfload)
215         WRITE(numout,*) ''
216
217      END IF
218      !
219
220      !---------------------------------------------------------------------------------------------------------------------
221      ! sanity check  ! issue ln_isfcav not yet known as well as l_isfoasis  => move this call in isf_stp ?
222      ! melt in the cavity without cavity
223      IF ( ln_isfcav_mlt .AND. (.NOT. ln_isfcav) ) &
224          &   CALL ctl_stop('ice shelf melt in the cavity activated (ln_isfcav_mlt) but no cavity detected in domcfg (ln_isfcav), STOP' )
225      !
226      ! ice sheet coupling without cavity
227      IF ( ln_isfcpl .AND. (.NOT. ln_isfcav) ) &
228         &   CALL ctl_stop('coupling with an ice sheet model detected (ln_isfcpl) but no cavity detected in domcfg (ln_isfcav), STOP' )
229      !
230      IF ( ln_isfcpl .AND. ln_isfcpl_cons .AND. ln_linssh ) &
231         &   CALL ctl_stop( 'The coupling between NEMO and an ice sheet model with the conservation option does not work with the linssh option' )
232      !
233      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' )
234      !
235      IF ( l_isfoasis .AND. ln_isf ) THEN
236         !
237         CALL ctl_stop( ' ln_ctl and ice shelf not tested' )
238         !
239         ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation
240         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' )
241         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' )
242         !
243         ! oasis melt computation not tested (coded but not tested)
244         IF ( ln_isfcav_mlt .OR. ln_isfpar_mlt ) THEN
245            IF ( TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis not tested' )
246            IF ( TRIM(cn_isfpar_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis not tested' )
247         END IF
248         !
249         ! oasis melt computation with cavity open and cavity parametrised (not coded)
250         IF ( ln_isfcav_mlt .AND. ln_isfpar_mlt ) THEN
251            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' )
252         END IF
253         !
254         ! compatibility ice shelf and vvl
255         IF( .NOT. ln_vvl_zstar .AND. ln_isf ) CALL ctl_stop( 'Only vvl_zstar has been tested with ice shelf cavity' )
256         !
257      END IF
258   END SUBROUTINE isf_ctl
259   !
260   SUBROUTINE isf_nam
261      !!---------------------------------------------------------------------
262      !!                  ***  ROUTINE isf_nam  ***
263      !!
264      !! ** Purpose :   Read ice shelf namelist cfg and ref
265      !!
266      !!----------------------------------------------------------------------
267      INTEGER               :: ios                  ! Local integer output status for namelist read
268      !!----------------------------------------------------------------------
269      NAMELIST/namisf/ ln_isf       ,                                                                               & 
270         &             ln_isfcav_mlt, cn_isfcav_mlt, cn_gammablk, rn_gammat0, rn_gammas0, rn_htbl, sn_isfcav_fwf,   &
271         &             ln_isfpar_mlt, cn_isfpar_mlt, sn_isfpar_fwf, sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff, &
272         &             ln_isfcpl    , nn_drown, ln_isfcpl_cons, ln_isfdebug, rn_vtide,                              &
273         &             cn_isfload   , cn_isfdir
274      !!----------------------------------------------------------------------
275      !
276      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
277      READ  ( numnam_ref, namisf, IOSTAT = ios, ERR = 901)
278901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namisf in reference namelist', lwp )
279      !
280      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
281      READ  ( numnam_cfg, namisf, IOSTAT = ios, ERR = 902 )
282902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namisf in configuration namelist', lwp )
283      IF(lwm) WRITE ( numond, namisf )
284
285   END SUBROUTINE isf_nam
286   !!
287   !!======================================================================
288END MODULE isfstp
Note: See TracBrowser for help on using the repository browser.