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 13662 for NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE/iceupdate.F90 – NEMO

Ignore:
Timestamp:
2020-10-22T20:49:56+02:00 (4 years ago)
Author:
clem
Message:

update to almost r4.0.4

Location:
NEMO/branches/2019/dev_r11842_SI3-10_EAP
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP

    • Property svn:externals
      •  

        old new  
        1 ^/utils/build/arch@HEAD       arch 
        2 ^/utils/build/makenemo@HEAD   makenemo 
        3 ^/utils/build/mk@HEAD         mk 
        4 ^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        6 ^/vendors/FCM@HEAD            ext/FCM 
        7 ^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         1^/utils/build/arch@12130      arch 
         2^/utils/build/makenemo@12191  makenemo 
         3^/utils/build/mk@11662        mk 
         4^/utils/tools_r4.0-HEAD@12672 tools 
         5^/vendors/AGRIF/dev@10586     ext/AGRIF 
         6^/vendors/FCM@10134           ext/FCM 
         7^/vendors/IOIPSL@9655         ext/IOIPSL 
         8 
         9# SETTE mapping (inactive) 
         10#^/utils/CI/sette@12135        sette 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/ICE/iceupdate.F90

    r11536 r13662  
    2525   USE traqsr         ! add penetration of solar flux in the calculation of heat budget 
    2626   USE icectl         ! sea-ice: control prints 
    27    USE bdy_oce , ONLY : ln_bdy 
     27   USE zdfdrg  , ONLY : ln_drgice_imp 
    2828   ! 
    2929   USE in_out_manager ! I/O manager 
     
    9292      ! 
    9393      INTEGER  ::   ji, jj, jl, jk   ! dummy loop indices 
    94       REAL(wp) ::   zqmass           ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
    9594      REAL(wp) ::   zqsr             ! New solar flux received by the ocean 
    96       REAL(wp), DIMENSION(jpi,jpj)     ::   z2d                  ! 2D workspace 
    97       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_cs, zalb_os     ! 3D workspace 
     95      REAL(wp), DIMENSION(jpi,jpj) ::   z2d                  ! 2D workspace 
    9896      !!--------------------------------------------------------------------- 
    9997      IF( ln_timing )   CALL timing_start('ice_update') 
     
    104102         WRITE(numout,*)'~~~~~~~~~~~~~~' 
    105103      ENDIF 
     104 
     105      ! Net heat flux on top of the ice-ocean (W.m-2) 
     106      !---------------------------------------------- 
     107      qt_atm_oi(:,:) = qns_tot(:,:) + qsr_tot(:,:)  
    106108 
    107109      ! --- case we bypass ice thermodynamics --- ! 
     
    117119         DO ji = 1, jpi 
    118120 
    119             ! Solar heat flux reaching the ocean = zqsr (W.m-2)  
     121            ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2)  
    120122            !--------------------------------------------------- 
    121123            zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 
     
    123125            ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2)  
    124126            !--------------------------------------------------- 
    125             zqmass           = hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) ! heat flux from snow is 0 (T=0 degC) 
    126             qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + zqmass + zqsr 
    127  
    128             ! Add the residual from heat diffusion equation and sublimation (W.m-2) 
    129             !---------------------------------------------------------------------- 
    130             qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + hfx_err_dif(ji,jj) +   & 
    131                &             ( hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) ) 
    132  
     127            qt_oce_ai(ji,jj) = qt_atm_oi(ji,jj) - hfx_sum(ji,jj) - hfx_bom(ji,jj) - hfx_bog(ji,jj) & 
     128               &                                - hfx_dif(ji,jj) - hfx_opw(ji,jj) - hfx_snw(ji,jj) & 
     129               &                                + hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) & 
     130               &                                + hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) + hfx_spr(ji,jj)                  
     131             
    133132            ! New qsr and qns used to compute the oceanic heat flux at the next time step 
    134133            !---------------------------------------------------------------------------- 
    135             qsr(ji,jj) = zqsr                                       
     134            ! if warming and some ice remains, then we suppose that the whole solar flux has been consumed to melt the ice 
     135            ! else ( cooling or no ice left ), then we suppose that     no    solar flux has been consumed 
     136            ! 
     137            IF( fhld(ji,jj) > 0._wp .AND. at_i(ji,jj) > 0._wp ) THEN   !-- warming and some ice remains 
     138               !                                        solar flux transmitted thru the 1st level of the ocean (i.e. not used by sea-ice) 
     139               qsr(ji,jj) = ( 1._wp - at_i_b(ji,jj) ) * qsr_oce(ji,jj) * ( 1._wp - frq_m(ji,jj) ) & 
     140                  !                                   + solar flux transmitted thru ice and the 1st ocean level (also not used by sea-ice) 
     141                  &             + SUM( a_i_b(ji,jj,:) * qtr_ice_bot(ji,jj,:) ) * ( 1._wp - frq_m(ji,jj) ) 
     142               ! 
     143            ELSE                                                       !-- cooling or no ice left 
     144               qsr(ji,jj) = zqsr 
     145            ENDIF 
     146            ! 
     147            ! the non-solar is simply derived from the solar flux 
    136148            qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr               
    137149 
     
    142154            ! Mass flux at the ocean surface       
    143155            !------------------------------------ 
    144             !  case of realistic freshwater flux (Tartinville et al., 2001) (presently ACTIVATED) 
    145             !  -------------------------------------------------------------------------------------  
    146             !  The idea of this approach is that the system that we consider is the ICE-OCEAN system 
    147             !  Thus  FW  flux  =  External ( E-P+snow melt) 
    148             !       Salt flux  =  Exchanges in the ice-ocean system then converted into FW 
    149             !                     Associated to Ice formation AND Ice melting 
    150             !                     Even if i see Ice melting as a FW and SALT flux 
    151             !         
    152             ! mass flux from ice/ocean 
     156            ! ice-ocean  mass flux 
    153157            wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
    154158               &           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) + wfx_pnd(ji,jj) 
    155159 
    156             ! add the snow melt water to snow mass flux to the ocean 
     160            ! snw-ocean mass flux 
    157161            wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) 
    158162 
    159             ! mass flux at the ocean/ice interface 
    160             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 
    161             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) 
    162  
     163            ! total mass flux at the ocean/ice interface 
     164            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 
     165            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 
    163166 
    164167            ! Salt flux at the ocean surface       
     
    185188      ! Snow/ice albedo (only if sent to coupler, useless in forced mode) 
    186189      !------------------------------------------------------------------ 
    187       CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_frac, h_ip, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos 
    188       ! 
    189       alb_ice(:,:,:) = ( 1._wp - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) 
     190      CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_eff, h_ip, cloud_fra, alb_ice ) ! ice albedo 
     191 
    190192      ! 
    191193      IF( lrst_ice ) THEN                       !* write snwice_mass fields in the restart file 
     
    266268      CALL iom_put ('hfxdif'     , hfx_dif     )   ! heat flux used for ice temperature change 
    267269      CALL iom_put ('hfxsnw'     , hfx_snw     )   ! heat flux used for snow melt  
    268       CALL iom_put ('hfxerr'     , hfx_err_dif )   ! heat flux error after heat diffusion (included in qt_oce_ai) 
     270      CALL iom_put ('hfxerr'     , hfx_err_dif )   ! heat flux error after heat diffusion 
    269271 
    270272      ! heat fluxes associated with mass exchange (freeze/melt/precip...) 
     
    283285      !--------- 
    284286#if ! defined key_agrif 
    285       IF( ln_icediachk .AND. .NOT. ln_bdy)   CALL ice_cons_final('iceupdate')                                       ! conservation 
     287      IF( ln_icediachk )   CALL ice_cons_final('iceupdate')                                       ! conservation 
    286288#endif 
    287       IF( ln_icectl                      )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    288       IF( ln_ctl                         )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    289       IF( ln_timing                      )   CALL timing_stop   ('ice_update')                                      ! timing 
     289      IF( ln_icectl    )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
     290      IF( ln_ctl       )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
     291      IF( ln_timing    )   CALL timing_stop   ('ice_update')                                      ! timing 
    290292      ! 
    291293   END SUBROUTINE ice_update_flx 
     
    323325      REAL(wp) ::   zat_u, zutau_ice, zu_t, zmodt   ! local scalar 
    324326      REAL(wp) ::   zat_v, zvtau_ice, zv_t, zrhoco  !   -      - 
     327      REAL(wp) ::   zflagi                          !   -      - 
    325328      !!--------------------------------------------------------------------- 
    326329      IF( ln_timing )   CALL timing_start('ice_update_tau') 
     
    355358      ! 
    356359      !                                      !==  every ocean time-step  ==! 
     360      IF ( ln_drgice_imp ) THEN 
     361         ! Save drag with right sign to update top drag in the ocean implicit friction  
     362         rCdU_ice(:,:) = -r1_rau0 * tmod_io(:,:) * at_i(:,:) * tmask(:,:,1)  
     363         zflagi = 0._wp 
     364      ELSE 
     365         zflagi = 1._wp 
     366      ENDIF 
    357367      ! 
    358368      DO jj = 2, jpjm1                                !* update the stress WITHOUT an ice-ocean rotation angle 
     
    364374               &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji  ,jj+1,1) ) 
    365375            !                                                   ! linearized quadratic drag formulation 
    366             zutau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * ( u_ice(ji,jj) - pu_oce(ji,jj) ) 
    367             zvtau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * ( v_ice(ji,jj) - pv_oce(ji,jj) ) 
     376            zutau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * ( u_ice(ji,jj) - zflagi * pu_oce(ji,jj) ) 
     377            zvtau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * ( v_ice(ji,jj) - zflagi * pv_oce(ji,jj) ) 
    368378            !                                                   ! stresses at the ocean surface 
    369379            utau(ji,jj) = ( 1._wp - zat_u ) * utau_oce(ji,jj) + zat_u * zutau_ice 
Note: See TracChangeset for help on using the changeset viewer.