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.
Changeset 14021 for NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/ICE/icectl.F90 – NEMO

Ignore:
Timestamp:
2020-12-02T20:53:00+01:00 (3 years ago)
Author:
laurent
Message:

Caught up with trunk rev 14020...

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/ICE/icectl.F90

    r13601 r14021  
    1212   !!   'key_si3'                                       SI3 sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    !!    ice_cons_hsm     : conservation tests on heat, salt and mass during a  time step (global)  
     14   !!    ice_cons_hsm     : conservation tests on heat, salt and mass during a  time step (global) 
    1515   !!    ice_cons_final   : conservation tests on heat, salt and mass at end of time step (global) 
    1616   !!    ice_cons2D       : conservation tests on heat, salt and mass at each gridcell 
     
    5555   CHARACTER(LEN=50)   ::   clname="icedrift_diagnostics.ascii"   ! ascii filename 
    5656   INTEGER             ::   numicedrift                           ! outfile unit 
    57    REAL(wp)            ::   rdiag_icemass, rdiag_icesalt, rdiag_iceheat  
    58    REAL(wp)            ::   rdiag_adv_icemass, rdiag_adv_icesalt, rdiag_adv_iceheat  
    59     
     57   REAL(wp)            ::   rdiag_icemass, rdiag_icesalt, rdiag_iceheat 
     58   REAL(wp)            ::   rdiag_adv_icemass, rdiag_adv_icesalt, rdiag_adv_iceheat 
     59 
    6060   !! * Substitutions 
    6161#  include "do_loop_substitute.h90" 
     
    7777      !!              It prints in ocean.output if there is a violation of conservation at each time-step 
    7878      !!              The thresholds (zchk_m, zchk_s, zchk_t) determine violations 
    79       !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
    80       !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
     79      !!              For salt and heat thresholds, ice is considered to have a salinity of 10 
     80      !!              and a heat content of 3e5 J/kg (=latent heat of fusion) 
    8181      !!------------------------------------------------------------------- 
    8282      INTEGER         , INTENT(in)    ::   icount        ! called at: =0 the begining of the routine, =1  the end 
     
    8585      !! 
    8686      REAL(wp) ::   zdiag_mass, zdiag_salt, zdiag_heat, & 
    87          &          zdiag_vmin, zdiag_amin, zdiag_amax, zdiag_eimin, zdiag_esmin, zdiag_smin 
     87         &          zdiag_vimin, zdiag_vsmin, zdiag_vpmin, zdiag_vlmin, zdiag_aimin, zdiag_aimax, & 
     88         &          zdiag_eimin, zdiag_esmin, zdiag_simin 
    8889      REAL(wp) ::   zvtrp, zetrp 
    8990      REAL(wp) ::   zarea 
     
    9293      IF( icount == 0 ) THEN 
    9394 
    94          pdiag_v = glob_sum( 'icectl',   SUM( v_i * rhoi + v_s * rhos, dim=3 ) * e1e2t ) 
     95         pdiag_v = glob_sum( 'icectl',   SUM( v_i * rhoi + v_s * rhos + ( v_ip + v_il ) * rhow, dim=3 ) * e1e2t ) 
    9596         pdiag_s = glob_sum( 'icectl',   SUM( sv_i * rhoi            , dim=3 ) * e1e2t ) 
    9697         pdiag_t = glob_sum( 'icectl', ( SUM( SUM( e_i, dim=4 ), dim=3 ) + SUM( SUM( e_s, dim=4 ), dim=3 ) ) * e1e2t ) 
     
    112113 
    113114         ! -- mass diag -- ! 
    114          zdiag_mass = ( glob_sum( 'icectl', SUM( v_i * rhoi + v_s * rhos, dim=3 ) * e1e2t ) - pdiag_v ) * r1_Dt_ice       & 
     115         zdiag_mass = ( glob_sum( 'icectl', SUM( v_i * rhoi + v_s * rhos + ( v_ip + v_il ) * rhow, dim=3 ) * e1e2t )      & 
     116            &            - pdiag_v ) * r1_Dt_ice                                                                          & 
    115117            &         + glob_sum( 'icectl', ( wfx_bog + wfx_bom + wfx_sum + wfx_sni + wfx_opw + wfx_res + wfx_dyn +       & 
    116118            &                                 wfx_lam + wfx_pnd + wfx_snw_sni + wfx_snw_sum + wfx_snw_dyn + wfx_snw_sub + & 
     
    132134 
    133135         ! -- min/max diag -- ! 
    134          zdiag_amax  = glob_max( 'icectl', SUM( a_i, dim=3 ) ) 
    135          zdiag_vmin  = glob_min( 'icectl', v_i ) 
    136          zdiag_amin  = glob_min( 'icectl', a_i ) 
    137          zdiag_smin  = glob_min( 'icectl', sv_i ) 
     136         zdiag_aimax = glob_max( 'icectl', SUM( a_i, dim=3 ) ) 
     137         zdiag_vimin = glob_min( 'icectl', v_i  ) 
     138         zdiag_vsmin = glob_min( 'icectl', v_s  ) 
     139         zdiag_vpmin = glob_min( 'icectl', v_ip ) 
     140         zdiag_vlmin = glob_min( 'icectl', v_il ) 
     141         zdiag_aimin = glob_min( 'icectl', a_i  ) 
     142         zdiag_simin = glob_min( 'icectl', sv_i ) 
    138143         zdiag_eimin = glob_min( 'icectl', SUM( e_i, dim=3 ) ) 
    139144         zdiag_esmin = glob_min( 'icectl', SUM( e_s, dim=3 ) ) 
     
    143148         zetrp = glob_sum( 'icectl', diag_adv_heat * e1e2t ) 
    144149 
    145          ! ice area (+epsi10 to set a threshold > 0 when there is no ice)  
     150         ! ice area (+epsi10 to set a threshold > 0 when there is no ice) 
    146151         zarea = glob_sum( 'icectl', SUM( a_i + epsi10, dim=3 ) * e1e2t ) 
    147152 
     
    155160               &                   WRITE(numout,*)   cd_routine,' : violation heat cons. [J]  = ',zdiag_heat * rDt_ice 
    156161            ! check negative values 
    157             IF( zdiag_vmin  < 0. ) WRITE(numout,*)   cd_routine,' : violation v_i < 0         = ',zdiag_vmin 
    158             IF( zdiag_amin  < 0. ) WRITE(numout,*)   cd_routine,' : violation a_i < 0         = ',zdiag_amin 
    159             IF( zdiag_smin  < 0. ) WRITE(numout,*)   cd_routine,' : violation s_i < 0         = ',zdiag_smin 
    160             IF( zdiag_eimin < 0. ) WRITE(numout,*)   cd_routine,' : violation e_i < 0         = ',zdiag_eimin 
    161             IF( zdiag_esmin < 0. ) WRITE(numout,*)   cd_routine,' : violation e_s < 0         = ',zdiag_esmin 
     162            IF( zdiag_vimin < 0. ) WRITE(numout,*)   cd_routine,' : violation v_i  < 0        = ',zdiag_vimin 
     163            IF( zdiag_vsmin < 0. ) WRITE(numout,*)   cd_routine,' : violation v_s  < 0        = ',zdiag_vsmin 
     164            IF( zdiag_vpmin < 0. ) WRITE(numout,*)   cd_routine,' : violation v_ip < 0        = ',zdiag_vpmin 
     165            IF( zdiag_vlmin < 0. ) WRITE(numout,*)   cd_routine,' : violation v_il < 0        = ',zdiag_vlmin 
     166            IF( zdiag_aimin < 0. ) WRITE(numout,*)   cd_routine,' : violation a_i  < 0        = ',zdiag_aimin 
     167            IF( zdiag_simin < 0. ) WRITE(numout,*)   cd_routine,' : violation s_i  < 0        = ',zdiag_simin 
     168            IF( zdiag_eimin < 0. ) WRITE(numout,*)   cd_routine,' : violation e_i  < 0        = ',zdiag_eimin 
     169            IF( zdiag_esmin < 0. ) WRITE(numout,*)   cd_routine,' : violation e_s  < 0        = ',zdiag_esmin 
    162170            ! check maximum ice concentration 
    163             IF( zdiag_amax > MAX(rn_amax_n,rn_amax_s)+epsi10 .AND. cd_routine /= 'icedyn_adv' .AND. cd_routine /= 'icedyn_rdgrft' ) & 
    164                &                   WRITE(numout,*)   cd_routine,' : violation a_i > amax      = ',zdiag_amax 
     171            IF( zdiag_aimax>MAX(rn_amax_n,rn_amax_s)+epsi10 .AND. cd_routine /= 'icedyn_adv' .AND. cd_routine /= 'icedyn_rdgrft' ) & 
     172               &                   WRITE(numout,*)   cd_routine,' : violation a_i > amax      = ',zdiag_aimax 
    165173            ! check if advection scheme is conservative 
    166174            IF( ABS(zvtrp) > zchk_m * rn_icechk_glo * zarea .AND. cd_routine == 'icedyn_adv' ) & 
    167                &                   WRITE(numout,*)   cd_routine,' : violation adv scheme [kg] = ',zvtrp * rdt_ice 
     175               &                   WRITE(numout,*)   cd_routine,' : violation adv scheme [kg] = ',zvtrp * rDt_ice 
    168176            IF( ABS(zetrp) > zchk_t * rn_icechk_glo * zarea .AND. cd_routine == 'icedyn_adv' ) & 
    169                &                   WRITE(numout,*)   cd_routine,' : violation adv scheme [J]  = ',zetrp * rdt_ice 
     177               &                   WRITE(numout,*)   cd_routine,' : violation adv scheme [J]  = ',zetrp * rDt_ice 
    170178         ENDIF 
    171179         ! 
     
    183191      !!              It prints in ocean.output if there is a violation of conservation at each time-step 
    184192      !!              The thresholds (zchk_m, zchk_s, zchk_t) determine the violations 
    185       !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
    186       !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
     193      !!              For salt and heat thresholds, ice is considered to have a salinity of 10 
     194      !!              and a heat content of 3e5 J/kg (=latent heat of fusion) 
    187195      !!------------------------------------------------------------------- 
    188196      CHARACTER(len=*), INTENT(in) ::   cd_routine    ! name of the routine 
     
    193201      ! water flux 
    194202      ! -- mass diag -- ! 
    195       zdiag_mass = glob_sum( 'icectl', (  wfx_ice   + wfx_snw   + wfx_spr + wfx_sub & 
    196          &                              + diag_vice + diag_vsnw - diag_adv_mass ) * e1e2t ) 
     203      zdiag_mass = glob_sum( 'icectl', (  wfx_ice   + wfx_snw   + wfx_spr   + wfx_sub + wfx_pnd & 
     204         &                              + diag_vice + diag_vsnw + diag_vpnd - diag_adv_mass ) * e1e2t ) 
    197205 
    198206      ! -- salt diag -- ! 
     
    200208 
    201209      ! -- heat diag -- ! 
    202       zdiag_heat  = glob_sum( 'icectl', ( qt_oce_ai - qt_atm_oi + diag_heat - diag_adv_heat ) * e1e2t ) 
     210      zdiag_heat = glob_sum( 'icectl', ( qt_oce_ai - qt_atm_oi + diag_heat - diag_adv_heat ) * e1e2t ) 
    203211      ! equivalent to this: 
    204212      !!zdiag_heat = glob_sum( 'icectl', ( -diag_heat + hfx_sum + hfx_bom + hfx_bog + hfx_dif + hfx_opw + hfx_snw & 
     
    206214      !!   &                                          ) * e1e2t ) 
    207215 
    208       ! ice area (+epsi10 to set a threshold > 0 when there is no ice)  
     216      ! ice area (+epsi10 to set a threshold > 0 when there is no ice) 
    209217      zarea = glob_sum( 'icectl', SUM( a_i + epsi10, dim=3 ) * e1e2t ) 
    210218 
     
    235243      !! 
    236244      REAL(wp), DIMENSION(jpi,jpj) ::   zdiag_mass, zdiag_salt, zdiag_heat, & 
    237          &                              zdiag_amin, zdiag_vmin, zdiag_smin, zdiag_emin !!, zdiag_amax   
     245         &                              zdiag_amin, zdiag_vmin, zdiag_smin, zdiag_emin !!, zdiag_amax 
    238246      INTEGER ::   jl, jk 
    239247      LOGICAL ::   ll_stop_m = .FALSE. 
     
    245253      IF( icount == 0 ) THEN 
    246254 
    247          pdiag_v = SUM( v_i  * rhoi + v_s * rhos, dim=3 ) 
    248          pdiag_s = SUM( sv_i * rhoi             , dim=3 ) 
     255         pdiag_v = SUM( v_i  * rhoi + v_s * rhos + ( v_ip + v_il ) * rhow, dim=3 ) 
     256         pdiag_s = SUM( sv_i * rhoi , dim=3 ) 
    249257         pdiag_t = SUM( SUM( e_i, dim=4 ), dim=3 ) + SUM( SUM( e_s, dim=4 ), dim=3 ) 
    250258 
     
    253261            &       wfx_snw_sni + wfx_snw_sum + wfx_snw_dyn + wfx_snw_sub + wfx_ice_sub + wfx_spr 
    254262         ! salt flux 
    255          pdiag_fs = sfx_bri + sfx_bog + sfx_bom + sfx_sum + sfx_sni + sfx_opw + sfx_res + sfx_dyn + sfx_sub + sfx_lam  
     263         pdiag_fs = sfx_bri + sfx_bog + sfx_bom + sfx_sum + sfx_sni + sfx_opw + sfx_res + sfx_dyn + sfx_sub + sfx_lam 
    256264         ! heat flux 
    257          pdiag_ft =   hfx_sum + hfx_bom + hfx_bog + hfx_dif + hfx_opw + hfx_snw  &  
     265         pdiag_ft =   hfx_sum + hfx_bom + hfx_bog + hfx_dif + hfx_opw + hfx_snw  & 
    258266            &       - hfx_thd - hfx_dyn - hfx_res - hfx_sub - hfx_spr 
    259267 
     
    261269 
    262270         ! -- mass diag -- ! 
    263          zdiag_mass =   ( SUM( v_i * rhoi + v_s * rhos, dim=3 ) - pdiag_v ) * r1_Dt_ice                             & 
     271         zdiag_mass =   ( SUM( v_i * rhoi + v_s * rhos + ( v_ip + v_il ) * rhow, dim=3 ) - pdiag_v ) * r1_Dt_ice    & 
    264272            &         + ( wfx_bog + wfx_bom + wfx_sum + wfx_sni + wfx_opw + wfx_res + wfx_dyn + wfx_lam + wfx_pnd + & 
    265273            &             wfx_snw_sni + wfx_snw_sum + wfx_snw_dyn + wfx_snw_sub + wfx_ice_sub + wfx_spr )           & 
     
    275283         ! -- heat diag -- ! 
    276284         zdiag_heat =   ( SUM( SUM( e_i, dim=4 ), dim=3 ) + SUM( SUM( e_s, dim=4 ), dim=3 ) - pdiag_t ) * r1_Dt_ice & 
    277             &         + (  hfx_sum + hfx_bom + hfx_bog + hfx_dif + hfx_opw + hfx_snw                                &  
     285            &         + (  hfx_sum + hfx_bom + hfx_bog + hfx_dif + hfx_opw + hfx_snw                                & 
    278286            &            - hfx_thd - hfx_dyn - hfx_res - hfx_sub - hfx_spr )                                        & 
    279287            &         - pdiag_ft 
     
    316324         IF( ll_stop_s )   CALL ctl_stop( 'STOP', cd_routine//': ice salt conservation issue' ) 
    317325         IF( ll_stop_t )   CALL ctl_stop( 'STOP', cd_routine//': ice heat conservation issue' ) 
    318           
     326 
    319327      ENDIF 
    320328 
     
    324332      !!--------------------------------------------------------------------- 
    325333      !!                 ***  ROUTINE ice_cons_wri  *** 
    326       !!         
    327       !! ** Purpose :   create a NetCDF file named cdfile_name which contains  
     334      !! 
     335      !! ** Purpose :   create a NetCDF file named cdfile_name which contains 
    328336      !!                the instantaneous fields when conservation issue occurs 
    329337      !! 
     
    332340      CHARACTER(len=*), INTENT( in ) ::   cdfile_name      ! name of the file created 
    333341      REAL(wp), DIMENSION(:,:), INTENT( in ) ::   pdiag_mass, pdiag_salt, pdiag_heat, & 
    334          &                                        pdiag_amin, pdiag_vmin, pdiag_smin, pdiag_emin !!, pdiag_amax   
     342         &                                        pdiag_amin, pdiag_vmin, pdiag_smin, pdiag_emin !!, pdiag_amax 
    335343      !! 
    336344      INTEGER ::   inum 
    337345      !!---------------------------------------------------------------------- 
    338       !  
     346      ! 
    339347      IF(lwp) WRITE(numout,*) 
    340348      IF(lwp) WRITE(numout,*) 'ice_cons_wri : single instantaneous ice state' 
    341349      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~  named :', cdfile_name, '...nc' 
    342       IF(lwp) WRITE(numout,*)                 
     350      IF(lwp) WRITE(numout,*) 
    343351 
    344352      CALL iom_open( TRIM(cdfile_name), inum, ldwrt = .TRUE., kdlev = jpl, cdcomp = 'ICE' ) 
    345        
     353 
    346354      CALL iom_rstput( 0, 0, inum, 'cons_mass', pdiag_mass(:,:) , ktype = jp_r8 )    ! ice mass spurious lost/gain 
    347355      CALL iom_rstput( 0, 0, inum, 'cons_salt', pdiag_salt(:,:) , ktype = jp_r8 )    ! ice salt spurious lost/gain 
    348356      CALL iom_rstput( 0, 0, inum, 'cons_heat', pdiag_heat(:,:) , ktype = jp_r8 )    ! ice heat spurious lost/gain 
    349357      ! other diags 
    350       CALL iom_rstput( 0, 0, inum, 'aneg_count', pdiag_amin(:,:) , ktype = jp_r8 )    !  
    351       CALL iom_rstput( 0, 0, inum, 'vneg_count', pdiag_vmin(:,:) , ktype = jp_r8 )    !  
    352       CALL iom_rstput( 0, 0, inum, 'sneg_count', pdiag_smin(:,:) , ktype = jp_r8 )    !  
    353       CALL iom_rstput( 0, 0, inum, 'eneg_count', pdiag_emin(:,:) , ktype = jp_r8 )    !  
    354        
     358      CALL iom_rstput( 0, 0, inum, 'aneg_count', pdiag_amin(:,:) , ktype = jp_r8 )    ! 
     359      CALL iom_rstput( 0, 0, inum, 'vneg_count', pdiag_vmin(:,:) , ktype = jp_r8 )    ! 
     360      CALL iom_rstput( 0, 0, inum, 'sneg_count', pdiag_smin(:,:) , ktype = jp_r8 )    ! 
     361      CALL iom_rstput( 0, 0, inum, 'eneg_count', pdiag_emin(:,:) , ktype = jp_r8 )    ! 
     362      ! mean state 
     363      CALL iom_rstput( 0, 0, inum, 'icecon'    , SUM(a_i ,dim=3) , ktype = jp_r8 )    ! 
     364      CALL iom_rstput( 0, 0, inum, 'icevol'    , SUM(v_i ,dim=3) , ktype = jp_r8 )    ! 
     365      CALL iom_rstput( 0, 0, inum, 'snwvol'    , SUM(v_s ,dim=3) , ktype = jp_r8 )    ! 
     366      CALL iom_rstput( 0, 0, inum, 'pndvol'    , SUM(v_ip,dim=3) , ktype = jp_r8 )    ! 
     367      CALL iom_rstput( 0, 0, inum, 'lidvol'    , SUM(v_il,dim=3) , ktype = jp_r8 )    ! 
     368 
    355369      CALL iom_close( inum ) 
    356370 
    357371   END SUBROUTINE ice_cons_wri 
    358     
     372 
    359373   SUBROUTINE ice_ctl( kt ) 
    360374      !!------------------------------------------------------------------- 
    361       !!                   ***  ROUTINE ice_ctl ***  
    362       !!                  
     375      !!                   ***  ROUTINE ice_ctl *** 
     376      !! 
    363377      !! ** Purpose :   control checks 
    364378      !!------------------------------------------------------------------- 
     
    372386      inb_alp(:) = 0 
    373387      ialert_id = 0 
    374        
     388 
    375389      ! Alert if very high salinity 
    376390      ialert_id = ialert_id + 1 ! reference number of this alert 
     
    416430         END_3D 
    417431      END DO 
    418    
     432 
    419433      ! Alert if very warm ice 
    420434      ialert_id = ialert_id + 1 ! reference number of this alert 
     
    430444         END_3D 
    431445      END DO 
    432        
     446 
    433447      ! Alerte if very thick ice 
    434448      ialert_id = ialert_id + 1 ! reference number of this alert 
    435449      cl_alname(ialert_id) = ' Very thick ice ' ! name of the alert 
    436       jl = jpl  
     450      jl = jpl 
    437451      DO_2D( 1, 1, 1, 1 ) 
    438452         IF( h_i(ji,jj,jl) > 50._wp ) THEN 
     
    446460      ialert_id = ialert_id + 1 ! reference number of this alert 
    447461      cl_alname(ialert_id) = ' Very thin ice ' ! name of the alert 
    448       jl = 1  
     462      jl = 1 
    449463      DO_2D( 1, 1, 1, 1 ) 
    450464         IF( h_i(ji,jj,jl) < rn_himin ) THEN 
     
    470484      cl_alname(ialert_id) = ' Ice on continents ' ! name of the alert 
    471485      DO_2D( 1, 1, 1, 1 ) 
    472          IF( tmask(ji,jj,1) == 0._wp .AND. ( at_i(ji,jj) > 0._wp .OR. vt_i(ji,jj) > 0._wp ) ) THEN  
     486         IF( tmask(ji,jj,1) == 0._wp .AND. ( at_i(ji,jj) > 0._wp .OR. vt_i(ji,jj) > 0._wp ) ) THEN 
    473487            WRITE(numout,*) ' ALERTE :   Ice on continents ',at_i(ji,jj),vt_i(ji,jj) 
    474488            WRITE(numout,*) ' at i,j = ',ji,jj 
     
    482496      DO_2D( 1, 1, 1, 1 ) 
    483497         IF(  ( vt_i(ji,jj) == 0._wp .AND. at_i(ji,jj) >  0._wp ) .OR. & 
    484             & ( vt_i(ji,jj) >  0._wp .AND. at_i(ji,jj) == 0._wp ) ) THEN  
     498            & ( vt_i(ji,jj) >  0._wp .AND. at_i(ji,jj) == 0._wp ) ) THEN 
    485499            WRITE(numout,*) ' ALERTE :   Incompatible ice conc and vol ',at_i(ji,jj),vt_i(ji,jj) 
    486500            WRITE(numout,*) ' at i,j = ',ji,jj 
     
    506520     ! 
    507521   END SUBROUTINE ice_ctl 
    508   
     522 
    509523   SUBROUTINE ice_prt( kt, ki, kj, kn, cd1 ) 
    510524      !!------------------------------------------------------------------- 
    511       !!                   ***  ROUTINE ice_prt ***  
    512       !!                  
    513       !! ** Purpose :   Writes global ice state on the (i,j) point  
    514       !!                in ocean.ouput  
    515       !!                3 possibilities exist  
     525      !!                   ***  ROUTINE ice_prt *** 
     526      !! 
     527      !! ** Purpose :   Writes global ice state on the (i,j) point 
     528      !!                in ocean.ouput 
     529      !!                3 possibilities exist 
    516530      !!                n = 1/-1 -> simple ice state 
    517531      !!                n = 2    -> exhaustive state 
    518532      !!                n = 3    -> ice/ocean salt fluxes 
    519533      !! 
    520       !! ** input   :   point coordinates (i,j)  
     534      !! ** input   :   point coordinates (i,j) 
    521535      !!                n : number of the option 
    522536      !!------------------------------------------------------------------- 
     
    536550            !  Simple state 
    537551            !---------------- 
    538              
     552 
    539553            IF ( kn == 1 .OR. kn == -1 ) THEN 
    540554               WRITE(numout,*) ' ice_prt - Point : ',ji,jj 
     
    552566               WRITE(numout,*) ' - Cell values ' 
    553567               WRITE(numout,*) '   ~~~~~~~~~~~ ' 
    554                WRITE(numout,*) ' at_i          : ', at_i(ji,jj)        
    555                WRITE(numout,*) ' ato_i         : ', ato_i(ji,jj)        
    556                WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj)        
    557                WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj)        
     568               WRITE(numout,*) ' at_i          : ', at_i(ji,jj) 
     569               WRITE(numout,*) ' ato_i         : ', ato_i(ji,jj) 
     570               WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj) 
     571               WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj) 
    558572               DO jl = 1, jpl 
    559573                  WRITE(numout,*) ' - Category (', jl,')' 
     
    578592            !  Exhaustive state 
    579593            !-------------------- 
    580              
     594 
    581595            IF ( kn .EQ. 2 ) THEN 
    582596               WRITE(numout,*) ' ice_prt - Point : ',ji,jj 
     
    584598               WRITE(numout,*) ' Exhaustive state ' 
    585599               WRITE(numout,*) ' lat - long ', gphit(ji,jj), glamt(ji,jj) 
    586                WRITE(numout,*)  
     600               WRITE(numout,*) 
    587601               WRITE(numout,*) ' - Cell values ' 
    588602               WRITE(numout,*) '   ~~~~~~~~~~~ ' 
    589                WRITE(numout,*) ' at_i          : ', at_i(ji,jj)        
    590                WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj)        
    591                WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj)        
     603               WRITE(numout,*) ' at_i          : ', at_i(ji,jj) 
     604               WRITE(numout,*) ' vt_i          : ', vt_i(ji,jj) 
     605               WRITE(numout,*) ' vt_s          : ', vt_s(ji,jj) 
    592606               WRITE(numout,*) ' u_ice(i-1,j)  : ', u_ice(ji-1,jj) 
    593607               WRITE(numout,*) ' u_ice(i  ,j)  : ', u_ice(ji,jj) 
     
    596610               WRITE(numout,*) ' strength      : ', strength(ji,jj) 
    597611               WRITE(numout,*) 
    598                 
     612 
    599613               DO jl = 1, jpl 
    600614                  WRITE(numout,*) ' - Category (',jl,')' 
    601                   WRITE(numout,*) '   ~~~~~~~~         '  
     615                  WRITE(numout,*) '   ~~~~~~~~         ' 
    602616                  WRITE(numout,*) ' h_i        : ', h_i(ji,jj,jl)              , ' h_s        : ', h_s(ji,jj,jl) 
    603617                  WRITE(numout,*) ' t_i        : ', t_i(ji,jj,1:nlay_i,jl) 
    604618                  WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl)             , ' t_s        : ', t_s(ji,jj,1:nlay_s,jl) 
    605619                  WRITE(numout,*) ' s_i        : ', s_i(ji,jj,jl)              , ' o_i        : ', o_i(ji,jj,jl) 
    606                   WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)              , ' a_i_b      : ', a_i_b(ji,jj,jl)    
    607                   WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)              , ' v_i_b      : ', v_i_b(ji,jj,jl)    
    608                   WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)              , ' v_s_b      : ', v_s_b(ji,jj,jl)   
    609                   WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)            , ' ei1        : ', e_i_b(ji,jj,1,jl)  
    610                   WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)            , ' ei2_b      : ', e_i_b(ji,jj,2,jl)   
    611                   WRITE(numout,*) ' e_snow     : ', e_s(ji,jj,1,jl)            , ' e_snow_b   : ', e_s_b(ji,jj,1,jl)  
    612                   WRITE(numout,*) ' sv_i       : ', sv_i(ji,jj,jl)             , ' sv_i_b     : ', sv_i_b(ji,jj,jl)    
     620                  WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)              , ' a_i_b      : ', a_i_b(ji,jj,jl) 
     621                  WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)              , ' v_i_b      : ', v_i_b(ji,jj,jl) 
     622                  WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)              , ' v_s_b      : ', v_s_b(ji,jj,jl) 
     623                  WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)            , ' ei1        : ', e_i_b(ji,jj,1,jl) 
     624                  WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)            , ' ei2_b      : ', e_i_b(ji,jj,2,jl) 
     625                  WRITE(numout,*) ' e_snow     : ', e_s(ji,jj,1,jl)            , ' e_snow_b   : ', e_s_b(ji,jj,1,jl) 
     626                  WRITE(numout,*) ' sv_i       : ', sv_i(ji,jj,jl)             , ' sv_i_b     : ', sv_i_b(ji,jj,jl) 
    613627               END DO !jl 
    614                 
     628 
    615629               WRITE(numout,*) 
    616630               WRITE(numout,*) ' - Heat / FW fluxes ' 
     
    620634               WRITE(numout,*) ' qns_ini       : ', (1._wp-at_i_b(ji,jj)) * qns(ji,jj) + SUM( a_i_b(ji,jj,:) * qns_ice(ji,jj,:) ) 
    621635               WRITE(numout,*) 
    622                WRITE(numout,*)  
    623                WRITE(numout,*) ' sst        : ', sst_m(ji,jj)   
    624                WRITE(numout,*) ' sss        : ', sss_m(ji,jj)   
    625                WRITE(numout,*)  
     636               WRITE(numout,*) 
     637               WRITE(numout,*) ' sst        : ', sst_m(ji,jj) 
     638               WRITE(numout,*) ' sss        : ', sss_m(ji,jj) 
     639               WRITE(numout,*) 
    626640               WRITE(numout,*) ' - Stresses ' 
    627641               WRITE(numout,*) '   ~~~~~~~~ ' 
    628                WRITE(numout,*) ' utau_ice   : ', utau_ice(ji,jj)  
     642               WRITE(numout,*) ' utau_ice   : ', utau_ice(ji,jj) 
    629643               WRITE(numout,*) ' vtau_ice   : ', vtau_ice(ji,jj) 
    630                WRITE(numout,*) ' utau       : ', utau    (ji,jj)  
     644               WRITE(numout,*) ' utau       : ', utau    (ji,jj) 
    631645               WRITE(numout,*) ' vtau       : ', vtau    (ji,jj) 
    632646            ENDIF 
    633              
     647 
    634648            !--------------------- 
    635649            ! Salt / heat fluxes 
    636650            !--------------------- 
    637              
     651 
    638652            IF ( kn .EQ. 3 ) THEN 
    639653               WRITE(numout,*) ' ice_prt - Point : ',ji,jj 
     
    650664               WRITE(numout,*) ' qt_atm_oi    : ', qt_atm_oi(ji,jj) 
    651665               WRITE(numout,*) ' qt_oce_ai    : ', qt_oce_ai(ji,jj) 
    652                WRITE(numout,*) ' dhc          : ', diag_heat(ji,jj)               
     666               WRITE(numout,*) ' dhc          : ', diag_heat(ji,jj) 
    653667               WRITE(numout,*) 
    654668               WRITE(numout,*) ' hfx_dyn      : ', hfx_dyn(ji,jj) 
    655669               WRITE(numout,*) ' hfx_thd      : ', hfx_thd(ji,jj) 
    656670               WRITE(numout,*) ' hfx_res      : ', hfx_res(ji,jj) 
    657                WRITE(numout,*) ' qsb_ice_bot  : ', qsb_ice_bot(ji,jj)  
     671               WRITE(numout,*) ' qsb_ice_bot  : ', qsb_ice_bot(ji,jj) 
    658672               WRITE(numout,*) ' qlead        : ', qlead(ji,jj) * r1_Dt_ice 
    659673               WRITE(numout,*) 
     
    666680               WRITE(numout,*) 
    667681               WRITE(numout,*) ' - Momentum fluxes ' 
    668                WRITE(numout,*) ' utau      : ', utau(ji,jj)  
     682               WRITE(numout,*) ' utau      : ', utau(ji,jj) 
    669683               WRITE(numout,*) ' vtau      : ', vtau(ji,jj) 
    670             ENDIF  
     684            ENDIF 
    671685            WRITE(numout,*) ' ' 
    672686            ! 
     
    680694      !!                  ***  ROUTINE ice_prt3D *** 
    681695      !! 
    682       !! ** Purpose : CTL prints of ice arrays in case sn_cfctl%prtctl is activated  
     696      !! ** Purpose : CTL prints of ice arrays in case sn_cfctl%prtctl is activated 
    683697      !! 
    684698      !!------------------------------------------------------------------- 
    685699      CHARACTER(len=*), INTENT(in) ::   cd_routine    ! name of the routine 
    686700      INTEGER                      ::   jk, jl        ! dummy loop indices 
    687        
     701 
    688702      CALL prt_ctl_info(' ========== ') 
    689703      CALL prt_ctl_info( cd_routine ) 
     
    704718      CALL prt_ctl(tab2d_1=delta_i    , clinfo1=' delta_i     :') 
    705719      CALL prt_ctl(tab2d_1=u_ice      , clinfo1=' u_ice       :', tab2d_2=v_ice      , clinfo2=' v_ice       :') 
    706         
     720 
    707721      DO jl = 1, jpl 
    708722         CALL prt_ctl_info(' ') 
     
    721735         CALL prt_ctl(tab2d_1=sv_i       (:,:,jl)        , clinfo1= ' sv_i        : ') 
    722736         CALL prt_ctl(tab2d_1=oa_i       (:,:,jl)        , clinfo1= ' oa_i        : ') 
    723           
     737 
    724738         DO jk = 1, nlay_i 
    725739            CALL prt_ctl_info(' - Layer : ', ivar=jk) 
     
    728742         END DO 
    729743      END DO 
    730        
     744 
    731745      CALL prt_ctl_info(' ') 
    732746      CALL prt_ctl_info(' - Stresses : ') 
     
    734748      CALL prt_ctl(tab2d_1=utau       , clinfo1= ' utau      : ', tab2d_2=vtau       , clinfo2= ' vtau      : ') 
    735749      CALL prt_ctl(tab2d_1=utau_ice   , clinfo1= ' utau_ice  : ', tab2d_2=vtau_ice   , clinfo2= ' vtau_ice  : ') 
    736        
     750 
    737751   END SUBROUTINE ice_prt3D 
    738752 
     
    776790      ! -- mass diag -- ! 
    777791      zdiag_mass     = glob_sum( 'icectl', (  wfx_ice   + wfx_snw   + wfx_spr + wfx_sub & 
    778          &                                  + diag_vice + diag_vsnw - diag_adv_mass ) * e1e2t ) * rdt_ice 
     792         &                                  + diag_vice + diag_vsnw - diag_adv_mass ) * e1e2t ) * rDt_ice 
    779793      zdiag_adv_mass = glob_sum( 'icectl', diag_adv_mass * e1e2t ) * rDt_ice 
    780794 
    781795      ! -- salt diag -- ! 
    782       zdiag_salt     = glob_sum( 'icectl', ( sfx + diag_sice - diag_adv_salt ) * e1e2t ) * rdt_ice * 1.e-3 
     796      zdiag_salt     = glob_sum( 'icectl', ( sfx + diag_sice - diag_adv_salt ) * e1e2t ) * rDt_ice * 1.e-3 
    783797      zdiag_adv_salt = glob_sum( 'icectl', diag_adv_salt * e1e2t ) * rDt_ice * 1.e-3 
    784798 
     
    839853      !!---------------------------------------------------------------------- 
    840854      !!                  ***  ROUTINE ice_drift_init  *** 
    841       !!                    
     855      !! 
    842856      !! ** Purpose :   create output file, initialise arrays 
    843857      !!---------------------------------------------------------------------- 
     
    865879      ! 
    866880   END SUBROUTINE ice_drift_init 
    867        
     881 
    868882#else 
    869883   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.