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 4634 for branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90 – NEMO

Ignore:
Timestamp:
2014-05-12T22:46:18+02:00 (10 years ago)
Author:
clem
Message:

major changes in heat budget

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r4345 r4634  
    5959   USE prtctl          ! Print control 
    6060   USE lib_fortran     !  
     61   USE cpl_oasis3, ONLY : lk_cpl 
    6162 
    6263#if defined key_bdy  
     
    133134      INTEGER, INTENT(in) ::   kblk    ! type of bulk (=3 CLIO, =4 CORE) 
    134135      !! 
    135       INTEGER  ::   jl      ! dummy loop index 
     136      INTEGER  ::   ji, jj, jl, jk      ! dummy loop index 
    136137      REAL(wp) ::   zcoef   ! local scalar 
    137138      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_ice_os, zalb_ice_cs  ! albedo of the ice under overcast/clear sky 
    138       REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_ice      ! mean albedo of ice (for coupled) 
     139      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_ice      ! mean albedo of ice  
    139140 
    140141      REAL(wp), POINTER, DIMENSION(:,:) :: zalb_ice_all    ! Mean albedo over all categories 
     
    146147      REAL(wp), POINTER, DIMENSION(:,:) :: z_dqns_ice_all  ! Mean d(qns)/dT over all categories 
    147148      REAL(wp), POINTER, DIMENSION(:,:) :: z_dqla_ice_all  ! Mean d(qla)/dT over all categories 
     149      REAL(wp) ::   ztmelts         ! clem 2014: for HC diags 
     150      REAL(wp)  ::   epsi20 = 1.e-20   ! 
    148151      !!---------------------------------------------------------------------- 
    149152 
     
    152155      IF( nn_timing == 1 )  CALL timing_start('sbc_ice_lim') 
    153156 
    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 
     157      CALL wrk_alloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs, zalb_ice ) 
     158 
     159      IF( lk_cpl ) THEN 
     160         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
     161            &   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) 
     162      ENDIF 
    161163 
    162164      IF( kt == nit000 ) THEN 
     
    168170         ! 
    169171         IF( ln_nicep ) THEN      ! control print at a given point 
    170             jiindx = 177   ;   jjindx = 112 
     172            jiindx = 3    ;   jjindx =  49 
    171173            IF(lwp) WRITE(numout,*) ' The debugging point is : jiindx : ',jiindx, ' jjindx : ',jjindx 
    172174         ENDIF 
     
    176178      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  ! 
    177179         !                                     !----------------------! 
    178          !                                           !  Bulk Formulea ! 
     180         !                                           !  Bulk Formulae ! 
    179181         !                                           !----------------! 
    180182         ! 
     
    192194         IF ( ln_cpl ) zalb_ice (:,:,:) = 0.5 * ( zalb_ice_cs (:,:,:) +  zalb_ice_os (:,:,:) ) 
    193195          
    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             ! 
     196         IF( lk_cpl ) THEN 
     197            IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) THEN 
     198               ! 
     199               ! Compute mean albedo and temperature 
     200               zalb_ice_all (:,:) = fice_ice_ave ( zalb_ice (:,:,:) )  
     201               ztem_ice_all (:,:) = fice_ice_ave ( tn_ice   (:,:,:) )  
     202               ! 
     203            ENDIF 
    201204         ENDIF 
    202 #endif 
    203205                                               ! Bulk formulea - provides the following fields: 
    204206         ! utau_ice, vtau_ice : surface ice stress                     (U- & V-points)   [N/m2] 
     
    218220            !          
    219221         CASE( 4 )                                       ! CORE bulk formulation 
    220             CALL blk_ice_core( t_su , u_ice     , v_ice     , zalb_ice_cs,               & 
     222            ! MV 2014 
     223            ! We must account for cloud fraction in the computation of the albedo 
     224            ! The present ref just uses the clear sky value 
     225            ! The overcast sky value is 0.06 higher, and polar skies are mostly overcast 
     226            ! CORE has no cloud fraction, hence we must prescribe it 
     227            ! Mean summer cloud fraction computed from CLIO = 0.81 
     228            zalb_ice(:,:,:) = 0.19 * zalb_ice_cs(:,:,:) + 0.81 * zalb_ice_os(:,:,:) 
     229            ! Following line, we replace zalb_ice_cs by simply zalb_ice 
     230            CALL blk_ice_core( t_su , u_ice     , v_ice     , zalb_ice   ,               & 
    221231               &                      utau_ice  , vtau_ice  , qns_ice    , qsr_ice   ,   & 
    222232               &                      qla_ice   , dqns_ice  , dqla_ice   ,               & 
     
    239249 
    240250         ! Average over all categories 
    241 #if defined key_coupled 
     251         IF( lk_cpl ) THEN 
    242252         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) THEN 
    243253 
     
    269279            END IF 
    270280         END IF 
    271 #endif 
     281         ENDIF 
    272282         !                                           !----------------------! 
    273283         !                                           ! LIM-3  time-stepping ! 
     
    285295         old_smv_i(:,:,:)   = smv_i(:,:,:)     ! salt content 
    286296         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 ??? 
     297         old_u_ice(:,:)     = u_ice(:,:) 
     298         old_v_ice(:,:)     = v_ice(:,:) 
     299 
     300         ! trends    !!gm is it truly necessary ??? 
    291301         d_a_i_thd  (:,:,:)   = 0._wp   ;   d_a_i_trp  (:,:,:)   = 0._wp 
    292302         d_v_i_thd  (:,:,:)   = 0._wp   ;   d_v_i_trp  (:,:,:)   = 0._wp 
     
    296306         d_smv_i_thd(:,:,:)   = 0._wp   ;   d_smv_i_trp(:,:,:)   = 0._wp 
    297307         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 
     308         d_u_ice_dyn(:,:)     = 0._wp   ;   d_v_ice_dyn(:,:)     = 0._wp 
     309 
     310         ! salt, heat and mass fluxes 
     311         sfx    (:,:) = 0._wp   ; 
     312         sfx_bri(:,:) = 0._wp   ;   sfx_dyn(:,:) = 0._wp   ;   sfx_res(:,:) = 0._wp 
     313         sfx_sni(:,:) = 0._wp   ;   sfx_opw(:,:) = 0._wp 
     314         sfx_bog(:,:) = 0._wp   ;   sfx_dyn(:,:) = 0._wp 
     315         sfx_bom(:,:) = 0._wp   ;   sfx_sum(:,:) = 0._wp 
     316 
     317         hfx_thd(:,:) = 0._wp   ;   hfx_dyn(:,:) = 0._wp   ;   hfx_snw(:,:) = 0._wp 
     318         hfx_tot(:,:) = 0._wp   ;   hfx_spr(:,:) = 0._wp   ;   hfx_res(:,:) = 0._wp 
     319         hfx_sub(:,:) = 0._wp   ;   hfx_err(:,:) = 0._wp   ;   hfx_in (:,:) = 0._wp   ;   hfx_out(:,:) = 0._wp 
     320         hfx_err_rem(:,:) = 0._wp 
     321 
     322         wfx_snw(:,:) = 0._wp   ;   wfx_ice(:,:) = 0._wp   ;   wfx_sub(:,:) = 0._wp 
     323         wfx_sni(:,:) = 0._wp   ;   wfx_opw(:,:) = 0._wp 
     324         wfx_bog(:,:) = 0._wp   ;   wfx_dyn(:,:) = 0._wp 
     325         wfx_bom(:,:) = 0._wp   ;   wfx_sum(:,:) = 0._wp 
     326         wfx_res(:,:) = 0._wp   ;    
     327         ! 
     328         fhld  (:,:) = 0._wp  
     329         fmmflx(:,:) = 0._wp      
     330         ftr_ice(:,:,:) = 0._wp   ! part of solar radiation transmitted through the ice 
     331 
     332         ! diags 
     333         diag_trp_vi(:,:) = 0._wp  ; diag_trp_vs(:,:) = 0._wp  ;  diag_trp_ei(:,:) = 0._wp  ;  diag_trp_es(:,:) = 0._wp  ;  
     334         diag_heat_dhc1(:,:) = 0._wp   ;    
     335 
    327336         ! dynamical invariants 
    328337         delta_i(:,:) = 0._wp       ;   divu_i(:,:) = 0._wp       ;   shear_i(:,:) = 0._wp 
     
    375384                          zcoef = rdt_ice /rday           !  Ice natural aging 
    376385                          oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * zcoef 
    377                           CALL lim_var_glo2eqv            ! this CALL is maybe not necessary (Martin) 
     386         !clem                 CALL lim_var_glo2eqv            ! this CALL is maybe not necessary (Martin) 
    378387         IF( ln_nicep )   CALL lim_prt_state( kt, jiindx, jjindx, 1, ' - ice thermodyn. - ' )   ! control print 
    379388                          CALL lim_itd_th( kt )           !  Remap ice categories, lateral accretion  ! 
     
    391400         !                                           ! Diagnostics and outputs  
    392401         IF (ln_limdiaout) CALL lim_diahsb 
    393 !clem # if ! defined key_iomput 
     402 
    394403                          CALL lim_wri( 1  )              ! Ice outputs  
    395 !clem # endif 
     404 
    396405         IF( kt == nit000 .AND. ln_rstart )   & 
    397406            &             CALL iom_close( numrir )        ! clem: close input ice restart file 
     
    413422       
    414423!!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 
     424      CALL wrk_dealloc( jpi,jpj,jpl, zalb_ice_os, zalb_ice_cs, zalb_ice ) 
     425 
     426      IF( lk_cpl ) THEN 
     427         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
     428            &    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) 
     429      ENDIF 
    423430      ! 
    424431      IF( nn_timing == 1 )  CALL timing_stop('sbc_ice_lim') 
     
    534541!                 WRITE(numout,*) ' sst                  : ', sst_m(ji,jj) 
    535542!                 WRITE(numout,*) ' sss                  : ', sss_m(ji,jj) 
    536 !                 WRITE(numout,*) ' s_i_newice           : ', s_i_newice(ji,jj,1:jpl) 
    537543!                 WRITE(numout,*)  
    538544                  inb_alp(ialert_id) = inb_alp(ialert_id) + 1 
     
    591597               !WRITE(numout,*) ' sst       : ', sst_m(ji,jj) 
    592598               !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)  
    606599               ! 
    607600               !CALL lim_prt_state( kt, ji, jj, 2, '   ') 
     
    790783               WRITE(numout,*) ' - Heat / FW fluxes ' 
    791784               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) 
     785               WRITE(numout,*) ' - Heat fluxes in and out the ice ***' 
     786               WRITE(numout,*) ' qsr_ini       : ', pfrld(ji,jj) * qsr(ji,jj) + SUM( old_a_i(ji,jj,:) * qsr_ice(ji,jj,:) ) 
     787               WRITE(numout,*) ' qns_ini       : ', pfrld(ji,jj) * qns(ji,jj) + SUM( old_a_i(ji,jj,:) * qns_ice(ji,jj,:) ) 
     788               WRITE(numout,*) 
    802789               WRITE(numout,*)  
    803790               WRITE(numout,*) ' sst        : ', sst_m(ji,jj)   
     
    829816               WRITE(numout,*) ' qsr       : ', qsr(ji,jj) 
    830817               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 
     818               WRITE(numout,*) 
     819               WRITE(numout,*) ' hfx_mass     : ', hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_snw(ji,jj) + hfx_res(ji,jj) 
     820               WRITE(numout,*) ' hfx_in       : ', hfx_in(ji,jj) 
     821               WRITE(numout,*) ' hfx_out      : ', hfx_out(ji,jj) 
     822               WRITE(numout,*) ' hfx_tot      : ', hfx_tot(ji,jj) 
     823               WRITE(numout,*) ' dhc          : ', diag_heat_dhc1(ji,jj)               
     824               WRITE(numout,*) 
     825               WRITE(numout,*) ' hfx_dyn      : ', hfx_dyn(ji,jj) 
     826               WRITE(numout,*) ' hfx_thd      : ', hfx_thd(ji,jj) 
     827               WRITE(numout,*) ' hfx_res      : ', hfx_res(ji,jj) 
     828               WRITE(numout,*) ' fhtur        : ', fhtur(ji,jj)  
     829               WRITE(numout,*) ' qlead        : ', qlead(ji,jj) * r1_rdtice 
    834830               WRITE(numout,*) 
    835831               WRITE(numout,*) ' - Salt fluxes at bottom interface ***' 
    836832               WRITE(numout,*) ' emp       : ', emp    (ji,jj) 
    837                WRITE(numout,*) ' sfx_bri   : ', sfx_bri(ji,jj) 
    838833               WRITE(numout,*) ' sfx       : ', sfx    (ji,jj) 
    839834               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) 
     835               WRITE(numout,*) ' sfx_bri   : ', sfx_bri(ji,jj) 
     836               WRITE(numout,*) ' sfx_dyn   : ', sfx_dyn(ji,jj) 
    843837               WRITE(numout,*) 
    844838               WRITE(numout,*) ' - Momentum fluxes ' 
    845839               WRITE(numout,*) ' utau      : ', utau(ji,jj)  
    846840               WRITE(numout,*) ' vtau      : ', vtau(ji,jj) 
    847             ENDIF 
     841            ENDIF  
    848842            WRITE(numout,*) ' ' 
    849843            ! 
Note: See TracChangeset for help on using the changeset viewer.