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 4924 for branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90 – NEMO

Ignore:
Timestamp:
2014-11-28T18:24:01+01:00 (9 years ago)
Author:
mathiot
Message:

UKM02_ice_shelves merged and SETTE tested with revision 4879 of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r4724 r4924  
    5959   USE prtctl          ! Print control 
    6060   USE lib_fortran     !  
     61   USE cpl_oasis3, ONLY : lk_cpl 
    6162 
    6263#if defined key_bdy  
     
    6869 
    6970   PUBLIC sbc_ice_lim  ! routine called by sbcmod.F90 
     71   PUBLIC lim_prt_state 
    7072    
    7173   !! * Substitutions 
     
    133135      INTEGER, INTENT(in) ::   kblk    ! type of bulk (=3 CLIO, =4 CORE) 
    134136      !! 
    135       INTEGER  ::   jl      ! dummy loop index 
     137      INTEGER  ::   ji, jj, jl, jk      ! dummy loop index 
    136138      REAL(wp) ::   zcoef   ! local scalar 
    137139      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_ice_os, zalb_ice_cs  ! albedo of the ice under overcast/clear sky 
     
    146148      REAL(wp), POINTER, DIMENSION(:,:) :: z_dqns_ice_all  ! Mean d(qns)/dT over all categories 
    147149      REAL(wp), POINTER, DIMENSION(:,:) :: z_dqla_ice_all  ! Mean d(qla)/dT over all categories 
     150      REAL(wp) ::   ztmelts           ! clem 2014: for HC diags 
     151      REAL(wp) ::   epsi20 = 1.e-20   ! 
    148152      !!---------------------------------------------------------------------- 
    149153 
     
    152156      IF( nn_timing == 1 )  CALL timing_start('sbc_ice_lim') 
    153157 
    154       CALL wrk_alloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs ) 
    155  
    156 #if defined key_coupled 
    157       IF ( ln_cpl .OR. ln_iceflx_ave .OR. ln_iceflx_linear ) CALL wrk_alloc( jpi,jpj,jpl, zalb_ice) 
    158       IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
    159          &   CALL wrk_alloc( jpi,jpj, ztem_ice_all, zalb_ice_all, z_qsr_ice_all, z_qns_ice_all, z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
    160 #endif 
     158      CALL wrk_alloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs, zalb_ice ) 
     159 
     160      IF( lk_cpl ) THEN 
     161         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
     162            &   CALL wrk_alloc( jpi, jpj, ztem_ice_all , zalb_ice_all  , z_qsr_ice_all, z_qns_ice_all,  & 
     163            &                            z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
     164      ENDIF 
    161165 
    162166      IF( kt == nit000 ) THEN 
     
    168172         ! 
    169173         IF( ln_nicep ) THEN      ! control print at a given point 
    170             jiindx = 177   ;   jjindx = 112 
     174            jiindx = 15    ;   jjindx =  44 
    171175            IF(lwp) WRITE(numout,*) ' The debugging point is : jiindx : ',jiindx, ' jjindx : ',jjindx 
    172176         ENDIF 
     
    176180      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  ! 
    177181         !                                     !----------------------! 
    178          !                                           !  Bulk Formulea ! 
     182         !                                           !  Bulk Formulae ! 
    179183         !                                           !----------------! 
    180184         ! 
    181185         u_oce(:,:) = ssu_m(:,:) * umask(:,:,1)                     ! mean surface ocean current at ice velocity point 
    182186         v_oce(:,:) = ssv_m(:,:) * vmask(:,:,1)                    ! (C-grid dynamics :  U- & V-points as the ocean) 
    183          ! 
    184          t_bo(:,:) = tfreez( sss_m ) +  rt0          ! masked sea surface freezing temperature [Kelvin] 
    185          !                                           ! (set to rt0 over land) 
     187 
     188         ! masked sea surface freezing temperature [Kelvin] 
     189         t_bo(:,:) = ( tfreez( sss_m ) +  rt0 ) * tmask(:,:,1) + rt0 * ( 1. - tmask(:,:,1) ) 
     190 
    186191         CALL albedo_ice( t_su, ht_i, ht_s, zalb_ice_cs, zalb_ice_os )  ! ... ice albedo 
    187192 
     
    192197         IF ( ln_cpl ) zalb_ice (:,:,:) = 0.5 * ( zalb_ice_cs (:,:,:) +  zalb_ice_os (:,:,:) ) 
    193198          
    194 #if defined key_coupled 
    195          IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) THEN 
    196             ! 
    197             ! Compute mean albedo and temperature 
    198             zalb_ice_all (:,:) = fice_ice_ave ( zalb_ice (:,:,:) )  
    199             ztem_ice_all (:,:) = fice_ice_ave ( tn_ice   (:,:,:) )  
    200             ! 
     199         IF( lk_cpl ) THEN 
     200            IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) THEN 
     201               ! 
     202               ! Compute mean albedo and temperature 
     203               zalb_ice_all (:,:) = fice_ice_ave ( zalb_ice (:,:,:) )  
     204               ztem_ice_all (:,:) = fice_ice_ave ( tn_ice   (:,:,:) )  
     205               ! 
     206            ENDIF 
    201207         ENDIF 
    202 #endif 
    203208                                               ! Bulk formulea - provides the following fields: 
    204209         ! utau_ice, vtau_ice : surface ice stress                     (U- & V-points)   [N/m2] 
     
    218223            !          
    219224         CASE( 4 )                                       ! CORE bulk formulation 
    220             CALL blk_ice_core( t_su , u_ice     , v_ice     , zalb_ice_cs,               & 
     225            ! MV 2014 
     226            ! We must account for cloud fraction in the computation of the albedo 
     227            ! The present ref just uses the clear sky value 
     228            ! The overcast sky value is 0.06 higher, and polar skies are mostly overcast 
     229            ! CORE has no cloud fraction, hence we must prescribe it 
     230            ! Mean summer cloud fraction computed from CLIO = 0.81 
     231            zalb_ice(:,:,:) = 0.19 * zalb_ice_cs(:,:,:) + 0.81 * zalb_ice_os(:,:,:) 
     232            ! Following line, we replace zalb_ice_cs by simply zalb_ice 
     233            CALL blk_ice_core( t_su , u_ice     , v_ice     , zalb_ice   ,               & 
    221234               &                      utau_ice  , vtau_ice  , qns_ice    , qsr_ice   ,   & 
    222235               &                      qla_ice   , dqns_ice  , dqla_ice   ,               & 
     
    239252 
    240253         ! Average over all categories 
    241 #if defined key_coupled 
     254         IF( lk_cpl ) THEN 
    242255         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) THEN 
    243256 
     
    269282            END IF 
    270283         END IF 
    271 #endif 
     284         ENDIF 
    272285         !                                           !----------------------! 
    273286         !                                           ! LIM-3  time-stepping ! 
     
    277290         ! 
    278291         !                                           ! Store previous ice values 
    279 !!gm : remark   old_...   should becomes ...b  as tn versus tb   
    280          old_a_i  (:,:,:)   = a_i  (:,:,:)     ! ice area 
    281          old_e_i  (:,:,:,:) = e_i  (:,:,:,:)   ! ice thermal energy 
    282          old_v_i  (:,:,:)   = v_i  (:,:,:)     ! ice volume 
    283          old_v_s  (:,:,:)   = v_s  (:,:,:)     ! snow volume  
    284          old_e_s  (:,:,:,:) = e_s  (:,:,:,:)   ! snow thermal energy 
    285          old_smv_i(:,:,:)   = smv_i(:,:,:)     ! salt content 
    286          old_oa_i (:,:,:)   = oa_i (:,:,:)     ! areal age content 
    287          ! 
    288          old_u_ice(:,:) = u_ice(:,:) 
    289          old_v_ice(:,:) = v_ice(:,:) 
    290          !                                           ! intialisation to zero    !!gm is it truly necessary ??? 
     292         a_i_b  (:,:,:)   = a_i  (:,:,:)     ! ice area 
     293         e_i_b  (:,:,:,:) = e_i  (:,:,:,:)   ! ice thermal energy 
     294         v_i_b  (:,:,:)   = v_i  (:,:,:)     ! ice volume 
     295         v_s_b  (:,:,:)   = v_s  (:,:,:)     ! snow volume  
     296         e_s_b  (:,:,:,:) = e_s  (:,:,:,:)   ! snow thermal energy 
     297         smv_i_b(:,:,:)   = smv_i(:,:,:)     ! salt content 
     298         oa_i_b (:,:,:)   = oa_i (:,:,:)     ! areal age content 
     299         u_ice_b(:,:)     = u_ice(:,:) 
     300         v_ice_b(:,:)     = v_ice(:,:) 
     301 
     302         ! trends    !!gm is it truly necessary ??? 
    291303         d_a_i_thd  (:,:,:)   = 0._wp   ;   d_a_i_trp  (:,:,:)   = 0._wp 
    292304         d_v_i_thd  (:,:,:)   = 0._wp   ;   d_v_i_trp  (:,:,:)   = 0._wp 
     
    296308         d_smv_i_thd(:,:,:)   = 0._wp   ;   d_smv_i_trp(:,:,:)   = 0._wp 
    297309         d_oa_i_thd (:,:,:)   = 0._wp   ;   d_oa_i_trp (:,:,:)   = 0._wp 
    298          ! 
    299          d_u_ice_dyn(:,:) = 0._wp 
    300          d_v_ice_dyn(:,:) = 0._wp 
    301          ! 
    302          sfx    (:,:) = 0._wp   ;   sfx_thd  (:,:) = 0._wp 
    303          sfx_bri(:,:) = 0._wp   ;   sfx_mec  (:,:) = 0._wp   ;   sfx_res  (:,:) = 0._wp 
    304          fhbri  (:,:) = 0._wp   ;   fheat_mec(:,:) = 0._wp   ;   fheat_res(:,:) = 0._wp 
    305          fhmec  (:,:) = 0._wp   ;    
    306          fmmec  (:,:) = 0._wp 
    307          fmmflx (:,:) = 0._wp      
    308          focea2D(:,:) = 0._wp 
    309          fsup2D (:,:) = 0._wp 
    310  
    311          ! used in limthd.F90 
    312          rdvosif(:,:) = 0._wp   ! variation of ice volume at surface 
    313          rdvobif(:,:) = 0._wp   ! variation of ice volume at bottom 
    314          fdvolif(:,:) = 0._wp   ! total variation of ice volume 
    315          rdvonif(:,:) = 0._wp   ! lateral variation of ice volume 
    316          fstric (:,:) = 0._wp   ! part of solar radiation transmitted through the ice 
    317          ffltbif(:,:) = 0._wp   ! linked with fstric 
    318          qfvbq  (:,:) = 0._wp   ! linked with fstric 
    319          rdm_snw(:,:) = 0._wp   ! variation of snow mass per unit area 
    320          rdm_ice(:,:) = 0._wp   ! variation of ice mass per unit area 
    321          hicifp (:,:) = 0._wp   ! daily thermodynamic ice production.  
    322          ! 
    323          diag_sni_gr(:,:) = 0._wp   ;   diag_lat_gr(:,:) = 0._wp 
    324          diag_bot_gr(:,:) = 0._wp   ;   diag_dyn_gr(:,:) = 0._wp 
    325          diag_bot_me(:,:) = 0._wp   ;   diag_sur_me(:,:) = 0._wp 
    326          diag_res_pr(:,:) = 0._wp   ;   diag_trp_vi(:,:) = 0._wp 
     310         d_u_ice_dyn(:,:)     = 0._wp   ;   d_v_ice_dyn(:,:)     = 0._wp 
     311 
     312         ! salt, heat and mass fluxes 
     313         sfx    (:,:) = 0._wp   ; 
     314         sfx_bri(:,:) = 0._wp   ;  
     315         sfx_sni(:,:) = 0._wp   ;   sfx_opw(:,:) = 0._wp 
     316         sfx_bog(:,:) = 0._wp   ;   sfx_dyn(:,:) = 0._wp 
     317         sfx_bom(:,:) = 0._wp   ;   sfx_sum(:,:) = 0._wp 
     318         sfx_res(:,:) = 0._wp 
     319 
     320         wfx_snw(:,:) = 0._wp   ;   wfx_ice(:,:) = 0._wp 
     321         wfx_sni(:,:) = 0._wp   ;   wfx_opw(:,:) = 0._wp 
     322         wfx_bog(:,:) = 0._wp   ;   wfx_dyn(:,:) = 0._wp 
     323         wfx_bom(:,:) = 0._wp   ;   wfx_sum(:,:) = 0._wp 
     324         wfx_res(:,:) = 0._wp   ;   wfx_sub(:,:) = 0._wp 
     325         wfx_spr(:,:) = 0._wp   ;    
     326 
     327         hfx_in (:,:) = 0._wp   ;   hfx_out(:,:) = 0._wp 
     328         hfx_thd(:,:) = 0._wp   ;    
     329         hfx_snw(:,:) = 0._wp   ;   hfx_opw(:,:) = 0._wp 
     330         hfx_bog(:,:) = 0._wp   ;   hfx_dyn(:,:) = 0._wp 
     331         hfx_bom(:,:) = 0._wp   ;   hfx_sum(:,:) = 0._wp 
     332         hfx_res(:,:) = 0._wp   ;   hfx_sub(:,:) = 0._wp 
     333         hfx_spr(:,:) = 0._wp   ;   hfx_dif(:,:) = 0._wp  
     334         hfx_err(:,:) = 0._wp   ;   hfx_err_rem(:,:) = 0._wp 
     335 
     336         ! 
     337         fhld  (:,:)    = 0._wp  
     338         fmmflx(:,:)    = 0._wp      
     339         ! part of solar radiation transmitted through the ice 
     340         ftr_ice(:,:,:) = 0._wp 
     341 
     342         ! diags 
     343         diag_trp_vi  (:,:) = 0._wp  ; diag_trp_vs(:,:) = 0._wp  ;  diag_trp_ei(:,:) = 0._wp  ;  diag_trp_es(:,:) = 0._wp 
     344         diag_heat_dhc(:,:) = 0._wp   
     345 
    327346         ! dynamical invariants 
    328347         delta_i(:,:) = 0._wp       ;   divu_i(:,:) = 0._wp       ;   shear_i(:,:) = 0._wp 
     
    352371         ENDIF 
    353372!                         !- Change old values for new values 
    354                           old_u_ice(:,:)   = u_ice (:,:) 
    355                           old_v_ice(:,:)   = v_ice (:,:) 
    356                           old_a_i(:,:,:)   = a_i (:,:,:) 
    357                           old_v_s(:,:,:)   = v_s (:,:,:) 
    358                           old_v_i(:,:,:)   = v_i (:,:,:) 
    359                           old_e_s(:,:,:,:) = e_s (:,:,:,:) 
    360                           old_e_i(:,:,:,:) = e_i (:,:,:,:) 
    361                           old_oa_i(:,:,:)  = oa_i(:,:,:) 
    362                           old_smv_i(:,:,:) = smv_i (:,:,:) 
     373                          u_ice_b(:,:)     = u_ice(:,:) 
     374                          v_ice_b(:,:)     = v_ice(:,:) 
     375                          a_i_b  (:,:,:)   = a_i (:,:,:) 
     376                          v_s_b  (:,:,:)   = v_s (:,:,:) 
     377                          v_i_b  (:,:,:)   = v_i (:,:,:) 
     378                          e_s_b  (:,:,:,:) = e_s (:,:,:,:) 
     379                          e_i_b  (:,:,:,:) = e_i (:,:,:,:) 
     380                          oa_i_b (:,:,:)   = oa_i (:,:,:) 
     381                          smv_i_b(:,:,:)   = smv_i(:,:,:) 
    363382  
    364383         ! ---------------------------------------------- 
     
    375394                          zcoef = rdt_ice /rday           !  Ice natural aging 
    376395                          oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * zcoef 
    377                           CALL lim_var_glo2eqv            ! this CALL is maybe not necessary (Martin) 
    378396         IF( ln_nicep )   CALL lim_prt_state( kt, jiindx, jjindx, 1, ' - ice thermodyn. - ' )   ! control print 
    379397                          CALL lim_itd_th( kt )           !  Remap ice categories, lateral accretion  ! 
     
    391409         !                                           ! Diagnostics and outputs  
    392410         IF (ln_limdiaout) CALL lim_diahsb 
    393 !clem # if ! defined key_iomput 
     411 
    394412                          CALL lim_wri( 1  )              ! Ice outputs  
    395 !clem # endif 
     413 
    396414         IF( kt == nit000 .AND. ln_rstart )   & 
    397415            &             CALL iom_close( numrir )        ! clem: close input ice restart file 
     
    413431       
    414432!!gm   remark, the ocean-ice stress is not saved in ice diag call above .....  find a solution!!! 
    415       ! 
    416       CALL wrk_dealloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs ) 
    417  
    418 #if defined key_coupled 
    419       IF ( ln_cpl .OR. ln_iceflx_ave .OR. ln_iceflx_linear ) CALL wrk_dealloc( jpi,jpj,jpl, zalb_ice) 
    420       IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
    421          &    CALL wrk_dealloc( jpi,jpj, ztem_ice_all, zalb_ice_all, z_qsr_ice_all, z_qns_ice_all, z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
    422 #endif 
     433      CALL wrk_dealloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs, zalb_ice ) 
     434 
     435      IF( lk_cpl ) THEN 
     436         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
     437            &    CALL wrk_dealloc( jpi, jpj, ztem_ice_all , zalb_ice_all , z_qsr_ice_all, z_qns_ice_all,   & 
     438            &                                z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
     439      ENDIF 
    423440      ! 
    424441      IF( nn_timing == 1 )  CALL timing_stop('sbc_ice_lim') 
     
    456473                  !WRITE(numout,*) ' at_i     ', at_i(ji,jj) 
    457474                  !WRITE(numout,*) ' Point - category', ji, jj, jl 
    458                   !WRITE(numout,*) ' a_i *** a_i_old ', a_i      (ji,jj,jl), old_a_i  (ji,jj,jl) 
    459                   !WRITE(numout,*) ' v_i *** v_i_old ', v_i      (ji,jj,jl), old_v_i  (ji,jj,jl) 
     475                  !WRITE(numout,*) ' a_i *** a_i_b   ', a_i      (ji,jj,jl), a_i_b  (ji,jj,jl) 
     476                  !WRITE(numout,*) ' v_i *** v_i_b   ', v_i      (ji,jj,jl), v_i_b  (ji,jj,jl) 
    460477                  !WRITE(numout,*) ' d_a_i_thd/trp   ', d_a_i_thd(ji,jj,jl), d_a_i_trp(ji,jj,jl) 
    461478                  !WRITE(numout,*) ' d_v_i_thd/trp   ', d_v_i_thd(ji,jj,jl), d_v_i_trp(ji,jj,jl) 
     
    534551!                 WRITE(numout,*) ' sst                  : ', sst_m(ji,jj) 
    535552!                 WRITE(numout,*) ' sss                  : ', sss_m(ji,jj) 
    536 !                 WRITE(numout,*) ' s_i_newice           : ', s_i_newice(ji,jj,1:jpl) 
    537553!                 WRITE(numout,*)  
    538554                  inb_alp(ialert_id) = inb_alp(ialert_id) + 1 
     
    568584               !DO jl = 1, jpl 
    569585                  !WRITE(numout,*) ' Category no: ', jl 
    570                   !WRITE(numout,*) ' a_i        : ', a_i      (ji,jj,jl) , ' old_a_i    : ', old_a_i  (ji,jj,jl)    
     586                  !WRITE(numout,*) ' a_i        : ', a_i      (ji,jj,jl) , ' a_i_b      : ', a_i_b  (ji,jj,jl)    
    571587                  !WRITE(numout,*) ' d_a_i_trp  : ', d_a_i_trp(ji,jj,jl) , ' d_a_i_thd  : ', d_a_i_thd(ji,jj,jl)  
    572                   !WRITE(numout,*) ' v_i        : ', v_i      (ji,jj,jl) , ' old_v_i    : ', old_v_i  (ji,jj,jl)    
     588                  !WRITE(numout,*) ' v_i        : ', v_i      (ji,jj,jl) , ' v_i_b      : ', v_i_b  (ji,jj,jl)    
    573589                  !WRITE(numout,*) ' d_v_i_trp  : ', d_v_i_trp(ji,jj,jl) , ' d_v_i_thd  : ', d_v_i_thd(ji,jj,jl)  
    574590                  !WRITE(numout,*) ' ' 
     
    591607               !WRITE(numout,*) ' sst       : ', sst_m(ji,jj) 
    592608               !WRITE(numout,*) ' sss       : ', sss_m(ji,jj) 
    593                !WRITE(numout,*) ' qcmif     : ', qcmif(ji,jj) 
    594                !WRITE(numout,*) ' qldif     : ', qldif(ji,jj) 
    595                !WRITE(numout,*) ' qcmif     : ', qcmif(ji,jj) / rdt_ice 
    596                !WRITE(numout,*) ' qldif     : ', qldif(ji,jj) / rdt_ice 
    597                !WRITE(numout,*) ' qfvbq     : ', qfvbq(ji,jj) 
    598                !WRITE(numout,*) ' qdtcn     : ', qdtcn(ji,jj) 
    599                !WRITE(numout,*) ' qfvbq / dt: ', qfvbq(ji,jj) / rdt_ice 
    600                !WRITE(numout,*) ' qdtcn / dt: ', qdtcn(ji,jj) / rdt_ice 
    601                !WRITE(numout,*) ' fdtcn     : ', fdtcn(ji,jj)  
    602                !WRITE(numout,*) ' fhmec     : ', fhmec(ji,jj)  
    603                !WRITE(numout,*) ' fheat_mec : ', fheat_mec(ji,jj)  
    604                !WRITE(numout,*) ' fheat_res : ', fheat_res(ji,jj)  
    605                !WRITE(numout,*) ' fhbri     : ', fhbri(ji,jj)  
    606609               ! 
    607610               !CALL lim_prt_state( kt, ji, jj, 2, '   ') 
     
    759762               WRITE(numout,*) ' strength      : ', strength(ji,jj) 
    760763               WRITE(numout,*) ' d_u_ice_dyn   : ', d_u_ice_dyn(ji,jj), ' d_v_ice_dyn   : ', d_v_ice_dyn(ji,jj) 
    761                WRITE(numout,*) ' old_u_ice     : ', old_u_ice(ji,jj)  , ' old_v_ice     : ', old_v_ice(ji,jj)   
     764               WRITE(numout,*) ' u_ice_b       : ', u_ice_b(ji,jj)    , ' v_ice_b       : ', v_ice_b(ji,jj)   
    762765               WRITE(numout,*) 
    763766                
     
    769772                  WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl)             , ' t_s        : ', t_s(ji,jj,1,jl) 
    770773                  WRITE(numout,*) ' sm_i       : ', sm_i(ji,jj,jl)             , ' o_i        : ', o_i(ji,jj,jl) 
    771                   WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)              , ' old_a_i    : ', old_a_i(ji,jj,jl)    
     774                  WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)              , ' a_i_b      : ', a_i_b(ji,jj,jl)    
    772775                  WRITE(numout,*) ' d_a_i_trp  : ', d_a_i_trp(ji,jj,jl)        , ' d_a_i_thd  : ', d_a_i_thd(ji,jj,jl)  
    773                   WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)              , ' old_v_i    : ', old_v_i(ji,jj,jl)    
     776                  WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)              , ' v_i_b      : ', v_i_b(ji,jj,jl)    
    774777                  WRITE(numout,*) ' d_v_i_trp  : ', d_v_i_trp(ji,jj,jl)        , ' d_v_i_thd  : ', d_v_i_thd(ji,jj,jl)  
    775                   WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)              , ' old_v_s    : ', old_v_s(ji,jj,jl)   
     778                  WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)              , ' v_s_b      : ', v_s_b(ji,jj,jl)   
    776779                  WRITE(numout,*) ' d_v_s_trp  : ', d_v_s_trp(ji,jj,jl)        , ' d_v_s_thd  : ', d_v_s_thd(ji,jj,jl) 
    777                   WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9      , ' old_ei1    : ', old_e_i(ji,jj,1,jl)/1.0e9  
     780                  WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9      , ' ei1        : ', e_i_b(ji,jj,1,jl)/1.0e9  
    778781                  WRITE(numout,*) ' de_i1_trp  : ', d_e_i_trp(ji,jj,1,jl)/1.0e9, ' de_i1_thd  : ', d_e_i_thd(ji,jj,1,jl)/1.0e9 
    779                   WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9      , ' old_ei2    : ', old_e_i(ji,jj,2,jl)/1.0e9   
     782                  WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9      , ' ei2_b      : ', e_i_b(ji,jj,2,jl)/1.0e9   
    780783                  WRITE(numout,*) ' de_i2_trp  : ', d_e_i_trp(ji,jj,2,jl)/1.0e9, ' de_i2_thd  : ', d_e_i_thd(ji,jj,2,jl)/1.0e9 
    781                   WRITE(numout,*) ' e_snow     : ', e_s(ji,jj,1,jl)            , ' old_e_snow : ', old_e_s(ji,jj,1,jl)  
     784                  WRITE(numout,*) ' e_snow     : ', e_s(ji,jj,1,jl)            , ' e_snow_b   : ', e_s_b(ji,jj,1,jl)  
    782785                  WRITE(numout,*) ' d_e_s_trp  : ', d_e_s_trp(ji,jj,1,jl)      , ' d_e_s_thd  : ', d_e_s_thd(ji,jj,1,jl) 
    783                   WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)            , ' old_smv_i  : ', old_smv_i(ji,jj,jl)    
     786                  WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)            , ' smv_i_b    : ', smv_i_b(ji,jj,jl)    
    784787                  WRITE(numout,*) ' d_smv_i_trp: ', d_smv_i_trp(ji,jj,jl)      , ' d_smv_i_thd: ', d_smv_i_thd(ji,jj,jl)  
    785                   WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl)             , ' old_oa_i   : ', old_oa_i(ji,jj,jl) 
     788                  WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl)             , ' oa_i_b     : ', oa_i_b(ji,jj,jl) 
    786789                  WRITE(numout,*) ' d_oa_i_trp : ', d_oa_i_trp(ji,jj,jl)       , ' d_oa_i_thd : ', d_oa_i_thd(ji,jj,jl) 
    787790               END DO !jl 
     
    790793               WRITE(numout,*) ' - Heat / FW fluxes ' 
    791794               WRITE(numout,*) '   ~~~~~~~~~~~~~~~~ ' 
    792                WRITE(numout,*) ' emp        : ', emp      (ji,jj) 
    793                WRITE(numout,*) ' sfx        : ', sfx      (ji,jj) 
    794                WRITE(numout,*) ' sfx_thd    : ', sfx_thd(ji,jj) 
    795                WRITE(numout,*) ' sfx_bri    : ', sfx_bri  (ji,jj) 
    796                WRITE(numout,*) ' sfx_mec    : ', sfx_mec  (ji,jj) 
    797                WRITE(numout,*) ' sfx_res    : ', sfx_res(ji,jj) 
    798                WRITE(numout,*) ' fmmec      : ', fmmec    (ji,jj) 
    799                WRITE(numout,*) ' fhmec      : ', fhmec    (ji,jj) 
    800                WRITE(numout,*) ' fhbri      : ', fhbri    (ji,jj) 
    801                WRITE(numout,*) ' fheat_mec  : ', fheat_mec(ji,jj) 
     795               WRITE(numout,*) ' - Heat fluxes in and out the ice ***' 
     796               WRITE(numout,*) ' qsr_ini       : ', pfrld(ji,jj) * qsr(ji,jj) + SUM( a_i_b(ji,jj,:) * qsr_ice(ji,jj,:) ) 
     797               WRITE(numout,*) ' qns_ini       : ', pfrld(ji,jj) * qns(ji,jj) + SUM( a_i_b(ji,jj,:) * qns_ice(ji,jj,:) ) 
     798               WRITE(numout,*) 
    802799               WRITE(numout,*)  
    803800               WRITE(numout,*) ' sst        : ', sst_m(ji,jj)   
     
    829826               WRITE(numout,*) ' qsr       : ', qsr(ji,jj) 
    830827               WRITE(numout,*) ' qns       : ', qns(ji,jj) 
    831                WRITE(numout,*) ' fdtcn     : ', fdtcn(ji,jj) 
    832                WRITE(numout,*) ' qcmif     : ', qcmif(ji,jj) * r1_rdtice 
    833                WRITE(numout,*) ' qldif     : ', qldif(ji,jj) * r1_rdtice 
     828               WRITE(numout,*) 
     829               WRITE(numout,*) ' hfx_mass     : ', hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_snw(ji,jj) + hfx_res(ji,jj) 
     830               WRITE(numout,*) ' hfx_in       : ', hfx_in(ji,jj) 
     831               WRITE(numout,*) ' hfx_out      : ', hfx_out(ji,jj) 
     832               WRITE(numout,*) ' dhc          : ', diag_heat_dhc(ji,jj)               
     833               WRITE(numout,*) 
     834               WRITE(numout,*) ' hfx_dyn      : ', hfx_dyn(ji,jj) 
     835               WRITE(numout,*) ' hfx_thd      : ', hfx_thd(ji,jj) 
     836               WRITE(numout,*) ' hfx_res      : ', hfx_res(ji,jj) 
     837               WRITE(numout,*) ' fhtur        : ', fhtur(ji,jj)  
     838               WRITE(numout,*) ' qlead        : ', qlead(ji,jj) * r1_rdtice 
    834839               WRITE(numout,*) 
    835840               WRITE(numout,*) ' - Salt fluxes at bottom interface ***' 
    836841               WRITE(numout,*) ' emp       : ', emp    (ji,jj) 
    837                WRITE(numout,*) ' sfx_bri   : ', sfx_bri(ji,jj) 
    838842               WRITE(numout,*) ' sfx       : ', sfx    (ji,jj) 
    839843               WRITE(numout,*) ' sfx_res   : ', sfx_res(ji,jj) 
    840                WRITE(numout,*) ' sfx_mec   : ', sfx_mec(ji,jj) 
    841                WRITE(numout,*) ' - Heat fluxes at bottom interface ***' 
    842                WRITE(numout,*) ' fheat_res : ', fheat_res(ji,jj) 
     844               WRITE(numout,*) ' sfx_bri   : ', sfx_bri(ji,jj) 
     845               WRITE(numout,*) ' sfx_dyn   : ', sfx_dyn(ji,jj) 
    843846               WRITE(numout,*) 
    844847               WRITE(numout,*) ' - Momentum fluxes ' 
    845848               WRITE(numout,*) ' utau      : ', utau(ji,jj)  
    846849               WRITE(numout,*) ' vtau      : ', vtau(ji,jj) 
    847             ENDIF 
     850            ENDIF  
    848851            WRITE(numout,*) ' ' 
    849852            ! 
Note: See TracChangeset for help on using the changeset viewer.