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.
icectl.F90 in NEMO/branches/UKMO/NEMO_4.0_GO6_mixing/src/ICE – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_GO6_mixing/src/ICE/icectl.F90

Last change on this file was 11083, checked in by davestorkey, 5 years ago

UKMO/NEMO_4.0_GO6_mixing : Update to be relative to rev 11081 of NEMO_4.0_mirror.

File size: 36.2 KB
Line 
1MODULE icectl
2   !!======================================================================
3   !!                     ***  MODULE  icectl  ***
4   !!   sea-ice : controls and prints
5   !!======================================================================
6   !! History :  3.5  !  2015-01  (M. Vancoppenolle) Original code
7   !!            3.7  !  2016-10  (C. Rousset)       Add routine ice_prt3D
8   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
9   !!----------------------------------------------------------------------
10#if defined key_si3
11   !!----------------------------------------------------------------------
12   !!   'key_si3'                                       SI3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!    ice_cons_hsm     : conservation tests on heat, salt and mass
15   !!    ice_cons_final   : conservation tests on heat, salt and mass at end of time step
16   !!    ice_ctl          : control prints in case of crash
17   !!    ice_prt          : control prints at a given grid point
18   !!    ice_prt3D        : control prints of ice arrays
19   !!----------------------------------------------------------------------
20   USE phycst         ! physical constants
21   USE oce            ! ocean dynamics and tracers
22   USE dom_oce        ! ocean space and time domain
23   USE ice            ! sea-ice: variables
24   USE ice1D          ! sea-ice: thermodynamics variables
25   USE sbc_oce        ! Surface boundary condition: ocean fields
26   USE sbc_ice        ! Surface boundary condition: ice   fields
27   !
28   USE in_out_manager ! I/O manager
29   USE lib_mpp        ! MPP library
30   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
31   USE timing         ! Timing
32   USE prtctl         ! Print control
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   ice_cons_hsm
38   PUBLIC   ice_cons_final
39   PUBLIC   ice_ctl
40   PUBLIC   ice_prt
41   PUBLIC   ice_prt3D
42
43   !! * Substitutions
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
47   !! $Id$
48   !! Software governed by the CeCILL license (see ./LICENSE)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE ice_cons_hsm( icount, cd_routine, pdiag_v, pdiag_s, pdiag_t, pdiag_fv, pdiag_fs, pdiag_ft )
53      !!-------------------------------------------------------------------
54      !!                       ***  ROUTINE ice_cons_hsm ***
55      !!
56      !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine
57      !!                     + test if ice concentration and volume are > 0
58      !!
59      !! ** Method  : This is an online diagnostics which can be activated with ln_icediachk=true
60      !!              It prints in ocean.output if there is a violation of conservation at each time-step
61      !!              The thresholds (zv_sill, zs_sill, zt_sill) which determine violations are set to
62      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
63      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
64      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
65      !!-------------------------------------------------------------------
66      INTEGER         , INTENT(in)    ::   icount        ! called at: =0 the begining of the routine, =1  the end
67      CHARACTER(len=*), INTENT(in)    ::   cd_routine    ! name of the routine
68      REAL(wp)        , INTENT(inout) ::   pdiag_v, pdiag_s, pdiag_t, pdiag_fv, pdiag_fs, pdiag_ft
69      !!
70      REAL(wp) ::   zv, zs, zt, zfs, zfv, zft
71      REAL(wp) ::   zvmin, zamin, zamax, zeimin, zesmin, zsmin
72      REAL(wp) ::   zvtrp, zetrp
73      REAL(wp) ::   zarea, zv_sill, zs_sill, zt_sill
74      REAL(wp), PARAMETER ::   zconv = 1.e-9 ! convert W to GW and kg to Mt
75      !!-------------------------------------------------------------------
76      !
77      IF( icount == 0 ) THEN
78         !                          ! water flux
79         pdiag_fv = glob_sum( 'icectl',                                                                       &
80            &                 -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) +                  &
81            &                    wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_pnd(:,:)  +  &
82            &                    wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) +  &
83            &                    wfx_ice_sub(:,:) + wfx_spr(:,:)  &
84            &                  ) * e1e2t(:,:) ) * zconv
85         !
86         !                          ! salt flux
87         pdiag_fs = glob_sum( 'icectl',                                                                     &
88            &                  ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
89            &                    sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    &
90            &                  ) *  e1e2t(:,:) ) * zconv 
91         !
92         !                          ! heat flux
93         pdiag_ft = glob_sum( 'icectl',                                                                    &
94            &                  ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
95            &                  - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
96            &                  ) *  e1e2t(:,:) ) * zconv
97
98         pdiag_v = glob_sum( 'icectl', SUM( v_i * rhoi + v_s * rhos, dim=3 ) * e1e2t * zconv )
99
100         pdiag_s = glob_sum( 'icectl', SUM( sv_i * rhoi            , dim=3 ) * e1e2t * zconv )
101
102         pdiag_t = glob_sum( 'icectl', (  SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 )     &
103            &                 + SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) ) * e1e2t ) * zconv
104
105      ELSEIF( icount == 1 ) THEN
106
107         ! water flux
108         zfv = glob_sum( 'icectl',                                                                        &
109            &             -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) +                  &
110            &                wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_pnd(:,:)  +  &
111            &                wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) +  &
112            &                wfx_ice_sub(:,:) + wfx_spr(:,:)  &
113            &              ) * e1e2t(:,:) ) * zconv - pdiag_fv
114
115         ! salt flux
116         zfs = glob_sum( 'icectl',                                                                       &
117            &              ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  &
118            &                sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:)    & 
119            &              ) * e1e2t(:,:) ) * zconv - pdiag_fs
120
121         ! heat flux
122         zft = glob_sum( 'icectl',                                                                      &
123            &              ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  & 
124            &              - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   &
125            &              ) * e1e2t(:,:) ) * zconv - pdiag_ft
126 
127         ! outputs
128         zv = ( ( glob_sum( 'icectl', SUM( v_i * rhoi + v_s * rhos, dim=3 ) * e1e2t ) * zconv  &
129            &     - pdiag_v ) * r1_rdtice - zfv ) * rday
130
131         zs = ( ( glob_sum( 'icectl', SUM( sv_i * rhoi            , dim=3 ) * e1e2t ) * zconv  &
132            &     - pdiag_s ) * r1_rdtice + zfs ) * rday
133
134         zt = ( glob_sum( 'icectl',                                                                &
135            &             (  SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 )                       &
136            &              + SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) ) * e1e2t ) * zconv   &
137            &   - pdiag_t ) * r1_rdtice + zft
138
139         ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative
140         zvtrp = glob_sum( 'icectl', ( diag_trp_vi * rhoi + diag_trp_vs * rhos ) * e1e2t  ) * zconv * rday 
141         zetrp = glob_sum( 'icectl', ( diag_trp_ei        + diag_trp_es        ) * e1e2t  ) * zconv
142
143         zamax  = glob_max( 'icectl', SUM( a_i, dim=3 ) )
144         zvmin  = glob_min( 'icectl', v_i )
145         zamin  = glob_min( 'icectl', a_i )
146         zsmin  = glob_min( 'icectl', sv_i )
147         zeimin = glob_min( 'icectl', SUM( e_i, dim=3 ) )
148         zesmin = glob_min( 'icectl', SUM( e_s, dim=3 ) )
149
150         ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
151         zarea   = glob_sum( 'icectl', SUM( a_i + epsi10, dim=3 ) * e1e2t ) * zconv ! in 1.e9 m2
152         zv_sill = zarea * 2.5e-5
153         zs_sill = zarea * 25.e-5
154         zt_sill = zarea * 10.e-5
155
156         IF(lwp) THEN
157            ! check conservation issues
158            IF ( ABS( zv ) > zv_sill )   WRITE(numout,*) 'violation volume [Mt/day]     (',cd_routine,') = ',zv
159            IF ( ABS( zs ) > zs_sill )   WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zs
160            IF ( ABS( zt ) > zt_sill )   WRITE(numout,*) 'violation enthalpy [GW]       (',cd_routine,') = ',zt
161            ! check maximum ice concentration
162            IF ( zamax > MAX( rn_amax_n,rn_amax_s)+epsi10 .AND. cd_routine /= 'icedyn_adv' .AND. cd_routine /= 'icedyn_rdgrft' )  &
163               &                         WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax
164            ! check negative values
165            IF ( zvmin  < 0. )           WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin
166            IF ( zamin  < 0. )           WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin
167            IF ( zsmin  < 0. )           WRITE(numout,*) 'violation s_i<0               (',cd_routine,') = ',zsmin
168            IF ( zeimin < 0. )           WRITE(numout,*) 'violation e_i<0               (',cd_routine,') = ',zeimin
169            IF ( zesmin < 0. )           WRITE(numout,*) 'violation e_s<0               (',cd_routine,') = ',zesmin
170!clem: the following check fails (I think...)
171!            IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'icedyn_adv' ) THEN
172!                                           WRITE(numout,*) 'violation vtrp [Mt/day]       (',cd_routine,') = ',zvtrp
173!                                           WRITE(numout,*) 'violation etrp [GW]           (',cd_routine,') = ',zetrp
174!            ENDIF
175         ENDIF
176         !
177      ENDIF
178
179   END SUBROUTINE ice_cons_hsm
180
181
182   SUBROUTINE ice_cons_final( cd_routine )
183      !!-------------------------------------------------------------------
184      !!                     ***  ROUTINE ice_cons_final ***
185      !!
186      !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step
187      !!
188      !! ** Method  : This is an online diagnostics which can be activated with ln_icediachk=true
189      !!              It prints in ocean.output if there is a violation of conservation at each time-step
190      !!              The thresholds (zv_sill, zs_sill, zt_sill) which determine the violation are set to
191      !!              a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years.
192      !!              For salt and heat thresholds, ice is considered to have a salinity of 10
193      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)
194      !!-------------------------------------------------------------------
195      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine
196      REAL(wp)                        :: zqmass, zhfx, zsfx, zvfx
197      REAL(wp)                        :: zarea, zv_sill, zs_sill, zt_sill
198      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt
199      !!-------------------------------------------------------------------
200
201      ! water flux
202      zvfx  = glob_sum( 'icectl', ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t ) * zconv * rday
203
204      ! salt flux
205      zsfx  = glob_sum( 'icectl', ( sfx + diag_sice ) * e1e2t ) * zconv * rday
206
207      ! heat flux
208      ! clem: not the good formulation
209      !!zhfx  = glob_sum( 'icectl', ( qt_oce_ai - qt_atm_oi + diag_heat + hfx_thd + hfx_dyn + hfx_res + hfx_sub + hfx_spr  &
210      !!   &                        ) * e1e2t ) * zconv
211
212      ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice)
213      zarea   = glob_sum( 'icectl', SUM( a_i + epsi10, dim=3 ) * e1e2t ) * zconv ! in 1.e9 m2
214      zv_sill = zarea * 2.5e-5
215      zs_sill = zarea * 25.e-5
216      zt_sill = zarea * 10.e-5
217
218      IF(lwp) THEN
219         IF( ABS( zvfx ) > zv_sill )   WRITE(numout,*) 'violation vfx  [Mt/day]       (',cd_routine,') = ',zvfx
220         IF( ABS( zsfx ) > zs_sill )   WRITE(numout,*) 'violation sfx  [psu*Mt/day]   (',cd_routine,') = ',zsfx
221         !!IF( ABS( zhfx ) > zt_sill )   WRITE(numout,*) 'violation hfx  [GW]           (',cd_routine,') = ',zhfx
222      ENDIF
223      !
224   END SUBROUTINE ice_cons_final
225
226   
227   SUBROUTINE ice_ctl( kt )
228      !!-------------------------------------------------------------------
229      !!                   ***  ROUTINE ice_ctl ***
230      !!                 
231      !! ** Purpose :   Alerts in case of model crash
232      !!-------------------------------------------------------------------
233      INTEGER, INTENT(in) ::   kt      ! ocean time step
234      INTEGER  ::   ji, jj, jk,  jl   ! dummy loop indices
235      INTEGER  ::   inb_altests       ! number of alert tests (max 20)
236      INTEGER  ::   ialert_id         ! number of the current alert
237      REAL(wp) ::   ztmelts           ! ice layer melting point
238      CHARACTER (len=30), DIMENSION(20) ::   cl_alname   ! name of alert
239      INTEGER           , DIMENSION(20) ::   inb_alp     ! number of alerts positive
240      !!-------------------------------------------------------------------
241
242      inb_altests = 10
243      inb_alp(:)  =  0
244
245      ! Alert if incompatible volume and concentration
246      ialert_id = 2 ! reference number of this alert
247      cl_alname(ialert_id) = ' Incompat vol and con         '    ! name of the alert
248
249      DO jl = 1, jpl
250         DO jj = 1, jpj
251            DO ji = 1, jpi
252               IF(  v_i(ji,jj,jl) /= 0._wp   .AND.   a_i(ji,jj,jl) == 0._wp   ) THEN
253                  !WRITE(numout,*) ' ALERTE 2 :   Incompatible volume and concentration '
254                  !WRITE(numout,*) ' at_i     ', at_i(ji,jj)
255                  !WRITE(numout,*) ' Point - category', ji, jj, jl
256                  !WRITE(numout,*) ' a_i *** a_i_b   ', a_i      (ji,jj,jl), a_i_b  (ji,jj,jl)
257                  !WRITE(numout,*) ' v_i *** v_i_b   ', v_i      (ji,jj,jl), v_i_b  (ji,jj,jl)
258                  inb_alp(ialert_id) = inb_alp(ialert_id) + 1
259               ENDIF
260            END DO
261         END DO
262      END DO
263
264      ! Alerte if very thick ice
265      ialert_id = 3 ! reference number of this alert
266      cl_alname(ialert_id) = ' Very thick ice               ' ! name of the alert
267      jl = jpl 
268      DO jj = 1, jpj
269         DO ji = 1, jpi
270            IF(   h_i(ji,jj,jl)  >  50._wp   ) THEN
271               !CALL ice_prt( kt, ji, jj, 2, ' ALERTE 3 :   Very thick ice ' )
272               inb_alp(ialert_id) = inb_alp(ialert_id) + 1
273            ENDIF
274         END DO
275      END DO
276
277      ! Alert if very fast ice
278      ialert_id = 4 ! reference number of this alert
279      cl_alname(ialert_id) = ' Very fast ice               ' ! name of the alert
280      DO jj = 1, jpj
281         DO ji = 1, jpi
282            IF(   MAX( ABS( u_ice(ji,jj) ), ABS( v_ice(ji,jj) ) ) > 1.5  .AND.  &
283               &  at_i(ji,jj) > 0._wp   ) THEN
284               !CALL ice_prt( kt, ji, jj, 1, ' ALERTE 4 :   Very fast ice ' )
285               !WRITE(numout,*) ' ice strength             : ', strength(ji,jj)
286               !WRITE(numout,*) ' oceanic stress utau      : ', utau(ji,jj)
287               !WRITE(numout,*) ' oceanic stress vtau      : ', vtau(ji,jj)
288               !WRITE(numout,*) ' sea-ice stress utau_ice  : ', utau_ice(ji,jj)
289               !WRITE(numout,*) ' sea-ice stress vtau_ice  : ', vtau_ice(ji,jj)
290               !WRITE(numout,*) ' sst                      : ', sst_m(ji,jj)
291               !WRITE(numout,*) ' sss                      : ', sss_m(ji,jj)
292               !WRITE(numout,*)
293               inb_alp(ialert_id) = inb_alp(ialert_id) + 1
294            ENDIF
295         END DO
296      END DO
297
298      ! Alert if there is ice on continents
299      ialert_id = 6 ! reference number of this alert
300      cl_alname(ialert_id) = ' Ice on continents           ' ! name of the alert
301      DO jj = 1, jpj
302         DO ji = 1, jpi
303            IF(   tmask(ji,jj,1) <= 0._wp   .AND.   at_i(ji,jj) > 0._wp   ) THEN 
304               !CALL ice_prt( kt, ji, jj, 1, ' ALERTE 6 :   Ice on continents ' )
305               !WRITE(numout,*) ' masks s, u, v        : ', tmask(ji,jj,1), umask(ji,jj,1), vmask(ji,jj,1)
306               !WRITE(numout,*) ' sst                  : ', sst_m(ji,jj)
307               !WRITE(numout,*) ' sss                  : ', sss_m(ji,jj)
308               !WRITE(numout,*) ' at_i(ji,jj)          : ', at_i(ji,jj)
309               !WRITE(numout,*) ' v_ice(ji,jj)         : ', v_ice(ji,jj)
310               !WRITE(numout,*) ' v_ice(ji,jj-1)       : ', v_ice(ji,jj-1)
311               !WRITE(numout,*) ' u_ice(ji-1,jj)       : ', u_ice(ji-1,jj)
312               !WRITE(numout,*) ' u_ice(ji,jj)         : ', v_ice(ji,jj)
313               !
314               inb_alp(ialert_id) = inb_alp(ialert_id) + 1
315            ENDIF
316         END DO
317      END DO
318
319!
320!     ! Alert if very fresh ice
321      ialert_id = 7 ! reference number of this alert
322      cl_alname(ialert_id) = ' Very fresh ice               ' ! name of the alert
323      DO jl = 1, jpl
324         DO jj = 1, jpj
325            DO ji = 1, jpi
326               IF( s_i(ji,jj,jl) < 0.1 .AND. a_i(ji,jj,jl) > 0._wp ) THEN
327!                 CALL ice_prt(kt,ji,jj,1, ' ALERTE 7 :   Very fresh ice ' )
328!                 WRITE(numout,*) ' sst                  : ', sst_m(ji,jj)
329!                 WRITE(numout,*) ' sss                  : ', sss_m(ji,jj)
330!                 WRITE(numout,*)
331                  inb_alp(ialert_id) = inb_alp(ialert_id) + 1
332               ENDIF
333            END DO
334         END DO
335      END DO
336!
337
338!     ! Alert if too old ice
339      ialert_id = 9 ! reference number of this alert
340      cl_alname(ialert_id) = ' Very old   ice               ' ! name of the alert
341      DO jl = 1, jpl
342         DO jj = 1, jpj
343            DO ji = 1, jpi
344               IF ( ( ( ABS( o_i(ji,jj,jl) ) > rdt_ice ) .OR. &
345                      ( ABS( o_i(ji,jj,jl) ) < 0._wp) ) .AND. &
346                             ( a_i(ji,jj,jl) > 0._wp ) ) THEN
347                  !CALL ice_prt( kt, ji, jj, 1, ' ALERTE 9 :   Wrong ice age ')
348                  inb_alp(ialert_id) = inb_alp(ialert_id) + 1
349               ENDIF
350            END DO
351         END DO
352      END DO
353 
354      ! Alert on salt flux
355      ialert_id = 5 ! reference number of this alert
356      cl_alname(ialert_id) = ' High salt flux               ' ! name of the alert
357      DO jj = 1, jpj
358         DO ji = 1, jpi
359            IF( ABS( sfx (ji,jj) ) > 1.0e-2 ) THEN  ! = 1 psu/day for 1m ocean depth
360               !CALL ice_prt( kt, ji, jj, 3, ' ALERTE 5 :   High salt flux ' )
361               !DO jl = 1, jpl
362                  !WRITE(numout,*) ' Category no: ', jl
363                  !WRITE(numout,*) ' a_i        : ', a_i      (ji,jj,jl) , ' a_i_b      : ', a_i_b  (ji,jj,jl)   
364                  !WRITE(numout,*) ' v_i        : ', v_i      (ji,jj,jl) , ' v_i_b      : ', v_i_b  (ji,jj,jl)   
365                  !WRITE(numout,*) ' '
366               !END DO
367               inb_alp(ialert_id) = inb_alp(ialert_id) + 1
368            ENDIF
369         END DO
370      END DO
371
372      ! Alert if qns very big
373      ialert_id = 8 ! reference number of this alert
374      cl_alname(ialert_id) = ' fnsolar very big             ' ! name of the alert
375      DO jj = 1, jpj
376         DO ji = 1, jpi
377            IF( ABS( qns(ji,jj) ) > 1500._wp .AND. at_i(ji,jj) > 0._wp ) THEN
378               !
379               !WRITE(numout,*) ' ALERTE 8 :   Very high non-solar heat flux'
380               !WRITE(numout,*) ' ji, jj    : ', ji, jj
381               !WRITE(numout,*) ' qns       : ', qns(ji,jj)
382               !WRITE(numout,*) ' sst       : ', sst_m(ji,jj)
383               !WRITE(numout,*) ' sss       : ', sss_m(ji,jj)
384               !
385               !CALL ice_prt( kt, ji, jj, 2, '   ')
386               inb_alp(ialert_id) = inb_alp(ialert_id) + 1
387               !
388            ENDIF
389         END DO
390      END DO
391      !+++++
392 
393      ! Alert if very warm ice
394      ialert_id = 10 ! reference number of this alert
395      cl_alname(ialert_id) = ' Very warm ice                ' ! name of the alert
396      inb_alp(ialert_id) = 0
397      DO jl = 1, jpl
398         DO jk = 1, nlay_i
399            DO jj = 1, jpj
400               DO ji = 1, jpi
401                  ztmelts    =  -rTmlt * sz_i(ji,jj,jk,jl) + rt0
402                  IF( t_i(ji,jj,jk,jl) >= ztmelts  .AND.  v_i(ji,jj,jl) > 1.e-10   &
403                     &                             .AND.  a_i(ji,jj,jl) > 0._wp   ) THEN
404                     !WRITE(numout,*) ' ALERTE 10 :   Very warm ice'
405                     !WRITE(numout,*) ' ji, jj, jk, jl : ', ji, jj, jk, jl
406                     !WRITE(numout,*) ' t_i : ', t_i(ji,jj,jk,jl)
407                     !WRITE(numout,*) ' e_i : ', e_i(ji,jj,jk,jl)
408                     !WRITE(numout,*) ' sz_i: ', sz_i(ji,jj,jk,jl)
409                     !WRITE(numout,*) ' ztmelts : ', ztmelts
410                     inb_alp(ialert_id) = inb_alp(ialert_id) + 1
411                  ENDIF
412               END DO
413            END DO
414         END DO
415      END DO
416
417      ! sum of the alerts on all processors
418      IF( lk_mpp ) THEN
419         DO ialert_id = 1, inb_altests
420            CALL mpp_sum('icectl', inb_alp(ialert_id))
421         END DO
422      ENDIF
423
424      ! print alerts
425      IF( lwp ) THEN
426         ialert_id = 1                                 ! reference number of this alert
427         cl_alname(ialert_id) = ' NO alerte 1      '   ! name of the alert
428         WRITE(numout,*) ' time step ',kt
429         WRITE(numout,*) ' All alerts at the end of ice model '
430         DO ialert_id = 1, inb_altests
431            WRITE(numout,*) ialert_id, cl_alname(ialert_id)//' : ', inb_alp(ialert_id), ' times ! '
432         END DO
433      ENDIF
434     !
435   END SUBROUTINE ice_ctl
436 
437   
438   SUBROUTINE ice_prt( kt, ki, kj, kn, cd1 )
439      !!-------------------------------------------------------------------
440      !!                   ***  ROUTINE ice_prt ***
441      !!                 
442      !! ** Purpose :   Writes global ice state on the (i,j) point
443      !!                in ocean.ouput
444      !!                3 possibilities exist
445      !!                n = 1/-1 -> simple ice state (plus Mechanical Check if -1)
446      !!                n = 2    -> exhaustive state
447      !!                n = 3    -> ice/ocean salt fluxes
448      !!
449      !! ** input   :   point coordinates (i,j)
450      !!                n : number of the option
451      !!-------------------------------------------------------------------
452      INTEGER         , INTENT(in) ::   kt            ! ocean time step
453      INTEGER         , INTENT(in) ::   ki, kj, kn    ! ocean gridpoint indices
454      CHARACTER(len=*), INTENT(in) ::   cd1           !
455      !!
456      INTEGER :: jl, ji, jj
457      !!-------------------------------------------------------------------
458
459      DO ji = mi0(ki), mi1(ki)
460         DO jj = mj0(kj), mj1(kj)
461
462            WRITE(numout,*) ' time step ',kt,' ',cd1             ! print title
463
464            !----------------
465            !  Simple state
466            !----------------
467           
468            IF ( kn == 1 .OR. kn == -1 ) THEN
469               WRITE(numout,*) ' ice_prt - Point : ',ji,jj
470               WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
471               WRITE(numout,*) ' Simple state '
472               WRITE(numout,*) ' masks s,u,v   : ', tmask(ji,jj,1), umask(ji,jj,1), vmask(ji,jj,1)
473               WRITE(numout,*) ' lat - long    : ', gphit(ji,jj), glamt(ji,jj)
474               WRITE(numout,*) ' - Ice drift   '
475               WRITE(numout,*) '   ~~~~~~~~~~~ '
476               WRITE(numout,*) ' u_ice(i-1,j)  : ', u_ice(ji-1,jj)
477               WRITE(numout,*) ' u_ice(i  ,j)  : ', u_ice(ji,jj)
478               WRITE(numout,*) ' v_ice(i  ,j-1): ', v_ice(ji,jj-1)
479               WRITE(numout,*) ' v_ice(i  ,j)  : ', v_ice(ji,jj)
480               WRITE(numout,*) ' strength      : ', strength(ji,jj)
481               WRITE(numout,*)
482               WRITE(numout,*) ' - Cell values '
483               WRITE(numout,*) '   ~~~~~~~~~~~ '
484               WRITE(numout,*) ' cell area     : ', e1e2t(ji,jj)
485               WRITE(numout,*) ' at_i          : ', at_i(ji,jj)       
486               WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj)       
487               WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj)       
488               DO jl = 1, jpl
489                  WRITE(numout,*) ' - Category (', jl,')'
490                  WRITE(numout,*) ' a_i           : ', a_i(ji,jj,jl)
491                  WRITE(numout,*) ' h_i           : ', h_i(ji,jj,jl)
492                  WRITE(numout,*) ' h_s           : ', h_s(ji,jj,jl)
493                  WRITE(numout,*) ' v_i           : ', v_i(ji,jj,jl)
494                  WRITE(numout,*) ' v_s           : ', v_s(ji,jj,jl)
495                  WRITE(numout,*) ' e_s           : ', e_s(ji,jj,1:nlay_s,jl)
496                  WRITE(numout,*) ' e_i           : ', e_i(ji,jj,1:nlay_i,jl)
497                  WRITE(numout,*) ' t_su          : ', t_su(ji,jj,jl)
498                  WRITE(numout,*) ' t_snow        : ', t_s(ji,jj,1:nlay_s,jl)
499                  WRITE(numout,*) ' t_i           : ', t_i(ji,jj,1:nlay_i,jl)
500                  WRITE(numout,*) ' s_i           : ', s_i(ji,jj,jl)
501                  WRITE(numout,*) ' sv_i          : ', sv_i(ji,jj,jl)
502                  WRITE(numout,*)
503               END DO
504            ENDIF
505            IF( kn == -1 ) THEN
506               WRITE(numout,*) ' Mechanical Check ************** '
507               WRITE(numout,*) ' Check what means ice divergence '
508               WRITE(numout,*) ' Total ice concentration ', at_i (ji,jj)
509               WRITE(numout,*) ' Total lead fraction     ', ato_i(ji,jj)
510               WRITE(numout,*) ' Sum of both             ', ato_i(ji,jj) + at_i(ji,jj)
511               WRITE(numout,*) ' Sum of both minus 1     ', ato_i(ji,jj) + at_i(ji,jj) - 1.00
512            ENDIF
513           
514
515            !--------------------
516            !  Exhaustive state
517            !--------------------
518           
519            IF ( kn .EQ. 2 ) THEN
520               WRITE(numout,*) ' ice_prt - Point : ',ji,jj
521               WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
522               WRITE(numout,*) ' Exhaustive state '
523               WRITE(numout,*) ' lat - long ', gphit(ji,jj), glamt(ji,jj)
524               WRITE(numout,*) 
525               WRITE(numout,*) ' - Cell values '
526               WRITE(numout,*) '   ~~~~~~~~~~~ '
527               WRITE(numout,*) ' cell area     : ', e1e2t(ji,jj)
528               WRITE(numout,*) ' at_i          : ', at_i(ji,jj)       
529               WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj)       
530               WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj)       
531               WRITE(numout,*) ' u_ice(i-1,j)  : ', u_ice(ji-1,jj)
532               WRITE(numout,*) ' u_ice(i  ,j)  : ', u_ice(ji,jj)
533               WRITE(numout,*) ' v_ice(i  ,j-1): ', v_ice(ji,jj-1)
534               WRITE(numout,*) ' v_ice(i  ,j)  : ', v_ice(ji,jj)
535               WRITE(numout,*) ' strength      : ', strength(ji,jj)
536               WRITE(numout,*) ' u_ice_b       : ', u_ice_b(ji,jj)    , ' v_ice_b       : ', v_ice_b(ji,jj) 
537               WRITE(numout,*)
538               
539               DO jl = 1, jpl
540                  WRITE(numout,*) ' - Category (',jl,')'
541                  WRITE(numout,*) '   ~~~~~~~~         ' 
542                  WRITE(numout,*) ' h_i        : ', h_i(ji,jj,jl)              , ' h_s        : ', h_s(ji,jj,jl)
543                  WRITE(numout,*) ' t_i        : ', t_i(ji,jj,1:nlay_i,jl)
544                  WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl)             , ' t_s        : ', t_s(ji,jj,1:nlay_s,jl)
545                  WRITE(numout,*) ' s_i        : ', s_i(ji,jj,jl)              , ' o_i        : ', o_i(ji,jj,jl)
546                  WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)              , ' a_i_b      : ', a_i_b(ji,jj,jl)   
547                  WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)              , ' v_i_b      : ', v_i_b(ji,jj,jl)   
548                  WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)              , ' v_s_b      : ', v_s_b(ji,jj,jl) 
549                  WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)            , ' ei1        : ', e_i_b(ji,jj,1,jl) 
550                  WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)            , ' ei2_b      : ', e_i_b(ji,jj,2,jl) 
551                  WRITE(numout,*) ' e_snow     : ', e_s(ji,jj,1,jl)            , ' e_snow_b   : ', e_s_b(ji,jj,1,jl) 
552                  WRITE(numout,*) ' sv_i       : ', sv_i(ji,jj,jl)             , ' sv_i_b     : ', sv_i_b(ji,jj,jl)   
553                  WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl)             , ' oa_i_b     : ', oa_i_b(ji,jj,jl)
554               END DO !jl
555               
556               WRITE(numout,*)
557               WRITE(numout,*) ' - Heat / FW fluxes '
558               WRITE(numout,*) '   ~~~~~~~~~~~~~~~~ '
559               WRITE(numout,*) ' - Heat fluxes in and out the ice ***'
560               WRITE(numout,*) ' qsr_ini       : ', (1._wp-at_i_b(ji,jj)) * qsr(ji,jj) + SUM( a_i_b(ji,jj,:) * qsr_ice(ji,jj,:) )
561               WRITE(numout,*) ' qns_ini       : ', (1._wp-at_i_b(ji,jj)) * qns(ji,jj) + SUM( a_i_b(ji,jj,:) * qns_ice(ji,jj,:) )
562               WRITE(numout,*)
563               WRITE(numout,*) 
564               WRITE(numout,*) ' sst        : ', sst_m(ji,jj) 
565               WRITE(numout,*) ' sss        : ', sss_m(ji,jj) 
566               WRITE(numout,*) 
567               WRITE(numout,*) ' - Stresses '
568               WRITE(numout,*) '   ~~~~~~~~ '
569               WRITE(numout,*) ' utau_ice   : ', utau_ice(ji,jj) 
570               WRITE(numout,*) ' vtau_ice   : ', vtau_ice(ji,jj)
571               WRITE(numout,*) ' utau       : ', utau    (ji,jj) 
572               WRITE(numout,*) ' vtau       : ', vtau    (ji,jj)
573            ENDIF
574           
575            !---------------------
576            ! Salt / heat fluxes
577            !---------------------
578           
579            IF ( kn .EQ. 3 ) THEN
580               WRITE(numout,*) ' ice_prt - Point : ',ji,jj
581               WRITE(numout,*) ' ~~~~~~~~~~~~~~ '
582               WRITE(numout,*) ' - Salt / Heat Fluxes '
583               WRITE(numout,*) '   ~~~~~~~~~~~~~~~~ '
584               WRITE(numout,*) ' lat - long ', gphit(ji,jj), glamt(ji,jj)
585               WRITE(numout,*)
586               WRITE(numout,*) ' - Heat fluxes at bottom interface ***'
587               WRITE(numout,*) ' qsr       : ', qsr(ji,jj)
588               WRITE(numout,*) ' qns       : ', qns(ji,jj)
589               WRITE(numout,*)
590               WRITE(numout,*) ' hfx_mass     : ', hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_snw(ji,jj) + hfx_res(ji,jj)
591               WRITE(numout,*) ' qt_atm_oi    : ', qt_atm_oi(ji,jj)
592               WRITE(numout,*) ' qt_oce_ai    : ', qt_oce_ai(ji,jj)
593               WRITE(numout,*) ' dhc          : ', diag_heat(ji,jj)             
594               WRITE(numout,*)
595               WRITE(numout,*) ' hfx_dyn      : ', hfx_dyn(ji,jj)
596               WRITE(numout,*) ' hfx_thd      : ', hfx_thd(ji,jj)
597               WRITE(numout,*) ' hfx_res      : ', hfx_res(ji,jj)
598               WRITE(numout,*) ' qsb_ice_bot  : ', qsb_ice_bot(ji,jj) 
599               WRITE(numout,*) ' qlead        : ', qlead(ji,jj) * r1_rdtice
600               WRITE(numout,*)
601               WRITE(numout,*) ' - Salt fluxes at bottom interface ***'
602               WRITE(numout,*) ' emp       : ', emp    (ji,jj)
603               WRITE(numout,*) ' sfx       : ', sfx    (ji,jj)
604               WRITE(numout,*) ' sfx_res   : ', sfx_res(ji,jj)
605               WRITE(numout,*) ' sfx_bri   : ', sfx_bri(ji,jj)
606               WRITE(numout,*) ' sfx_dyn   : ', sfx_dyn(ji,jj)
607               WRITE(numout,*)
608               WRITE(numout,*) ' - Momentum fluxes '
609               WRITE(numout,*) ' utau      : ', utau(ji,jj) 
610               WRITE(numout,*) ' vtau      : ', vtau(ji,jj)
611            ENDIF
612            WRITE(numout,*) ' '
613            !
614         END DO
615      END DO
616      !
617   END SUBROUTINE ice_prt
618
619   SUBROUTINE ice_prt3D( cd_routine )
620      !!-------------------------------------------------------------------
621      !!                  ***  ROUTINE ice_prt3D ***
622      !!
623      !! ** Purpose : CTL prints of ice arrays in case ln_ctl is activated
624      !!
625      !!-------------------------------------------------------------------
626      CHARACTER(len=*), INTENT(in)  :: cd_routine    ! name of the routine
627      INTEGER                       :: jk, jl        ! dummy loop indices
628     
629      CALL prt_ctl_info(' ========== ')
630      CALL prt_ctl_info( cd_routine )
631      CALL prt_ctl_info(' ========== ')
632      CALL prt_ctl_info(' - Cell values : ')
633      CALL prt_ctl_info('   ~~~~~~~~~~~~~ ')
634      CALL prt_ctl(tab2d_1=e1e2t      , clinfo1=' cell area   :')
635      CALL prt_ctl(tab2d_1=at_i       , clinfo1=' at_i        :')
636      CALL prt_ctl(tab2d_1=ato_i      , clinfo1=' ato_i       :')
637      CALL prt_ctl(tab2d_1=vt_i       , clinfo1=' vt_i        :')
638      CALL prt_ctl(tab2d_1=vt_s       , clinfo1=' vt_s        :')
639      CALL prt_ctl(tab2d_1=divu_i     , clinfo1=' divu_i      :')
640      CALL prt_ctl(tab2d_1=delta_i    , clinfo1=' delta_i     :')
641      CALL prt_ctl(tab2d_1=stress1_i  , clinfo1=' stress1_i   :')
642      CALL prt_ctl(tab2d_1=stress2_i  , clinfo1=' stress2_i   :')
643      CALL prt_ctl(tab2d_1=stress12_i , clinfo1=' stress12_i  :')
644      CALL prt_ctl(tab2d_1=strength   , clinfo1=' strength    :')
645      CALL prt_ctl(tab2d_1=delta_i    , clinfo1=' delta_i     :')
646      CALL prt_ctl(tab2d_1=u_ice      , clinfo1=' u_ice       :', tab2d_2=v_ice      , clinfo2=' v_ice       :')
647       
648      DO jl = 1, jpl
649         CALL prt_ctl_info(' ')
650         CALL prt_ctl_info(' - Category : ', ivar1=jl)
651         CALL prt_ctl_info('   ~~~~~~~~~~')
652         CALL prt_ctl(tab2d_1=h_i        (:,:,jl)        , clinfo1= ' h_i         : ')
653         CALL prt_ctl(tab2d_1=h_s        (:,:,jl)        , clinfo1= ' h_s         : ')
654         CALL prt_ctl(tab2d_1=t_su       (:,:,jl)        , clinfo1= ' t_su        : ')
655         CALL prt_ctl(tab2d_1=t_s        (:,:,1,jl)      , clinfo1= ' t_snow      : ')
656         CALL prt_ctl(tab2d_1=s_i        (:,:,jl)        , clinfo1= ' s_i         : ')
657         CALL prt_ctl(tab2d_1=o_i        (:,:,jl)        , clinfo1= ' o_i         : ')
658         CALL prt_ctl(tab2d_1=a_i        (:,:,jl)        , clinfo1= ' a_i         : ')
659         CALL prt_ctl(tab2d_1=v_i        (:,:,jl)        , clinfo1= ' v_i         : ')
660         CALL prt_ctl(tab2d_1=v_s        (:,:,jl)        , clinfo1= ' v_s         : ')
661         CALL prt_ctl(tab2d_1=e_i        (:,:,1,jl)      , clinfo1= ' e_i1        : ')
662         CALL prt_ctl(tab2d_1=e_s        (:,:,1,jl)      , clinfo1= ' e_snow      : ')
663         CALL prt_ctl(tab2d_1=sv_i       (:,:,jl)        , clinfo1= ' sv_i        : ')
664         CALL prt_ctl(tab2d_1=oa_i       (:,:,jl)        , clinfo1= ' oa_i        : ')
665         
666         DO jk = 1, nlay_i
667            CALL prt_ctl_info(' - Layer : ', ivar1=jk)
668            CALL prt_ctl(tab2d_1=t_i(:,:,jk,jl) , clinfo1= ' t_i       : ')
669         END DO
670      END DO
671     
672      CALL prt_ctl_info(' ')
673      CALL prt_ctl_info(' - Heat / FW fluxes : ')
674      CALL prt_ctl_info('   ~~~~~~~~~~~~~~~~~~ ')
675      CALL prt_ctl(tab2d_1=sst_m  , clinfo1= ' sst   : ', tab2d_2=sss_m     , clinfo2= ' sss       : ')
676      CALL prt_ctl(tab2d_1=qsr    , clinfo1= ' qsr   : ', tab2d_2=qns       , clinfo2= ' qns       : ')
677      CALL prt_ctl(tab2d_1=emp    , clinfo1= ' emp   : ', tab2d_2=sfx       , clinfo2= ' sfx       : ')
678     
679      CALL prt_ctl_info(' ')
680      CALL prt_ctl_info(' - Stresses : ')
681      CALL prt_ctl_info('   ~~~~~~~~~~ ')
682      CALL prt_ctl(tab2d_1=utau       , clinfo1= ' utau      : ', tab2d_2=vtau       , clinfo2= ' vtau      : ')
683      CALL prt_ctl(tab2d_1=utau_ice   , clinfo1= ' utau_ice  : ', tab2d_2=vtau_ice   , clinfo2= ' vtau_ice  : ')
684     
685   END SUBROUTINE ice_prt3D
686
687#else
688   !!----------------------------------------------------------------------
689   !!   Default option         Empty Module           No SI3 sea-ice model
690   !!----------------------------------------------------------------------
691#endif
692
693   !!======================================================================
694END MODULE icectl
Note: See TracBrowser for help on using the repository browser.