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 branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icectl.F90 @ 8514

Last change on this file since 8514 was 8514, checked in by clem, 7 years ago

changes in style - part5 - almost done

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