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 13694 for NEMO/branches/2020/r12377_ticket2386/src/ICE/iceupdate.F90 – NEMO

Ignore:
Timestamp:
2020-10-28T18:03:31+01:00 (3 years ago)
Author:
andmirek
Message:

Ticket #2386: merge with trunk rev 13688

Location:
NEMO/branches/2020/r12377_ticket2386
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r12377_ticket2386

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette@13507        sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/r12377_ticket2386/src/ICE/iceupdate.F90

    r13540 r13694  
    2424   USE traqsr         ! add penetration of solar flux in the calculation of heat budget 
    2525   USE icectl         ! sea-ice: control prints 
    26    USE bdy_oce , ONLY : ln_bdy 
    2726   USE zdfdrg  , ONLY : ln_drgice_imp 
    2827   ! 
     
    9291      ! 
    9392      INTEGER  ::   ji, jj, jl, jk   ! dummy loop indices 
    94       REAL(wp) ::   zqmass           ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
    9593      REAL(wp) ::   zqsr             ! New solar flux received by the ocean 
    9694      REAL(wp), DIMENSION(jpi,jpj) ::   z2d                  ! 2D workspace 
     
    103101         WRITE(numout,*)'~~~~~~~~~~~~~~' 
    104102      ENDIF 
     103 
     104      ! Net heat flux on top of the ice-ocean (W.m-2) 
     105      !---------------------------------------------- 
     106      qt_atm_oi(:,:) = qns_tot(:,:) + qsr_tot(:,:)  
    105107 
    106108      ! --- case we bypass ice thermodynamics --- ! 
     
    115117      DO_2D( 1, 1, 1, 1 ) 
    116118 
    117          ! Solar heat flux reaching the ocean = zqsr (W.m-2)  
     119         ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2)  
    118120         !--------------------------------------------------- 
    119121         zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 
     
    121123         ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2)  
    122124         !--------------------------------------------------- 
    123          zqmass           = hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) ! heat flux from snow is 0 (T=0 degC) 
    124          qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + zqmass + zqsr 
    125  
    126          ! Add the residual from heat diffusion equation and sublimation (W.m-2) 
    127          !---------------------------------------------------------------------- 
    128          qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + hfx_err_dif(ji,jj) +   & 
    129             &             ( hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) ) 
    130  
     125         qt_oce_ai(ji,jj) = qt_atm_oi(ji,jj) - hfx_sum(ji,jj) - hfx_bom(ji,jj) - hfx_bog(ji,jj) & 
     126            &                                - hfx_dif(ji,jj) - hfx_opw(ji,jj) - hfx_snw(ji,jj) & 
     127            &                                + hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) & 
     128            &                                + hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) + hfx_spr(ji,jj)                  
     129          
    131130         ! New qsr and qns used to compute the oceanic heat flux at the next time step 
    132131         !---------------------------------------------------------------------------- 
    133          qsr(ji,jj) = zqsr                                       
     132         ! if warming and some ice remains, then we suppose that the whole solar flux has been consumed to melt the ice 
     133         ! else ( cooling or no ice left ), then we suppose that     no    solar flux has been consumed 
     134         ! 
     135         IF( fhld(ji,jj) > 0._wp .AND. at_i(ji,jj) > 0._wp ) THEN   !-- warming and some ice remains 
     136            !                                        solar flux transmitted thru the 1st level of the ocean (i.e. not used by sea-ice) 
     137            qsr(ji,jj) = ( 1._wp - at_i_b(ji,jj) ) * qsr_oce(ji,jj) * ( 1._wp - frq_m(ji,jj) ) & 
     138               !                                   + solar flux transmitted thru ice and the 1st ocean level (also not used by sea-ice) 
     139               &             + SUM( a_i_b(ji,jj,:) * qtr_ice_bot(ji,jj,:) ) * ( 1._wp - frq_m(ji,jj) ) 
     140            ! 
     141         ELSE                                                       !-- cooling or no ice left 
     142            qsr(ji,jj) = zqsr 
     143         ENDIF 
     144         ! 
     145         ! the non-solar is simply derived from the solar flux 
    134146         qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr               
    135  
     147          
    136148         ! Mass flux at the atm. surface        
    137149         !----------------------------------- 
     
    140152         ! Mass flux at the ocean surface       
    141153         !------------------------------------ 
    142          !  case of realistic freshwater flux (Tartinville et al., 2001) (presently ACTIVATED) 
    143          !  -------------------------------------------------------------------------------------  
    144          !  The idea of this approach is that the system that we consider is the ICE-OCEAN system 
    145          !  Thus  FW  flux  =  External ( E-P+snow melt) 
    146          !       Salt flux  =  Exchanges in the ice-ocean system then converted into FW 
    147          !                     Associated to Ice formation AND Ice melting 
    148          !                     Even if i see Ice melting as a FW and SALT flux 
    149          !         
    150          ! mass flux from ice/ocean 
     154         ! ice-ocean  mass flux 
    151155         wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
    152156            &           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) + wfx_pnd(ji,jj) 
    153  
    154          ! add the snow melt water to snow mass flux to the ocean 
     157          
     158         ! snw-ocean mass flux 
    155159         wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) 
    156  
    157          ! mass flux at the ocean/ice interface 
    158          fmmflx(ji,jj) = - ( wfx_ice(ji,jj) + wfx_snw(ji,jj) + wfx_err_sub(ji,jj) )              ! F/M mass flux save at least for biogeochemical model 
    159          emp(ji,jj)    = emp_oce(ji,jj) - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_err_sub(ji,jj)   ! mass flux + F/M mass flux (always ice/ocean mass exchange) 
    160  
     160          
     161         ! total mass flux at the ocean/ice interface 
     162         fmmflx(ji,jj) =                - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_err_sub(ji,jj)   ! ice-ocean mass flux saved at least for biogeochemical model 
     163         emp   (ji,jj) = emp_oce(ji,jj) - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_err_sub(ji,jj)   ! atm-ocean + ice-ocean mass flux 
    161164 
    162165         ! Salt flux at the ocean surface       
     
    262265      CALL iom_put ('hfxdif'     , hfx_dif     )   ! heat flux used for ice temperature change 
    263266      CALL iom_put ('hfxsnw'     , hfx_snw     )   ! heat flux used for snow melt  
    264       CALL iom_put ('hfxerr'     , hfx_err_dif )   ! heat flux error after heat diffusion (included in qt_oce_ai) 
     267      CALL iom_put ('hfxerr'     , hfx_err_dif )   ! heat flux error after heat diffusion 
    265268 
    266269      ! heat fluxes associated with mass exchange (freeze/melt/precip...) 
     
    279282      !--------- 
    280283#if ! defined key_agrif 
    281       IF( ln_icediachk .AND. .NOT. ln_bdy)   CALL ice_cons_final('iceupdate')                                       ! conservation 
     284      IF( ln_icediachk      )   CALL ice_cons_final('iceupdate')                                       ! conservation 
    282285#endif 
    283       IF( ln_icectl                      )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    284       IF( sn_cfctl%l_prtctl              )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    285       IF( ln_timing                      )   CALL timing_stop   ('ice_update')                                      ! timing 
     286      IF( ln_icectl         )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
     287      IF( sn_cfctl%l_prtctl )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
     288      IF( ln_timing         )   CALL timing_stop   ('ice_update')                                      ! timing 
    286289      ! 
    287290   END SUBROUTINE ice_update_flx 
Note: See TracChangeset for help on using the changeset viewer.