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 12377 for NEMO/trunk/src/ICE/iceupdate.F90 – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/ICE/iceupdate.F90

    r11536 r12377  
    1515   !!   ice_update_tau   : update i- and j-stresses, and its modulus at the ocean surface 
    1616   !!---------------------------------------------------------------------- 
    17    USE oce     , ONLY : sshn, sshb 
    1817   USE phycst         ! physical constants 
    1918   USE dom_oce        ! ocean domain 
     
    4544 
    4645   !! * Substitutions 
    47 #  include "vectopt_loop_substitute.h90" 
     46#  include "do_loop_substitute.h90" 
    4847   !!---------------------------------------------------------------------- 
    4948   !! NEMO/ICE 4.0 , NEMO Consortium (2018) 
     
    114113      ENDIF 
    115114       
    116       DO jj = 1, jpj 
    117          DO ji = 1, jpi 
    118  
    119             ! Solar heat flux reaching the ocean = zqsr (W.m-2)  
    120             !--------------------------------------------------- 
    121             zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 
    122  
    123             ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2)  
    124             !--------------------------------------------------- 
    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  
    133             ! New qsr and qns used to compute the oceanic heat flux at the next time step 
    134             !---------------------------------------------------------------------------- 
    135             qsr(ji,jj) = zqsr                                       
    136             qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr               
    137  
    138             ! Mass flux at the atm. surface        
    139             !----------------------------------- 
    140             wfx_sub(ji,jj) = wfx_snw_sub(ji,jj) + wfx_ice_sub(ji,jj) 
    141  
    142             ! Mass flux at the ocean surface       
    143             !------------------------------------ 
    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 
    153             wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
    154                &           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) + wfx_pnd(ji,jj) 
    155  
    156             ! add the snow melt water to snow mass flux to the ocean 
    157             wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) 
    158  
    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  
    164             ! Salt flux at the ocean surface       
    165             !------------------------------------------ 
    166             sfx(ji,jj) = sfx_bog(ji,jj) + sfx_bom(ji,jj) + sfx_sum(ji,jj) + sfx_sni(ji,jj) + sfx_opw(ji,jj)   & 
    167                &       + sfx_res(ji,jj) + sfx_dyn(ji,jj) + sfx_bri(ji,jj) + sfx_sub(ji,jj) + sfx_lam(ji,jj) 
    168              
    169             ! Mass of snow and ice per unit area    
    170             !---------------------------------------- 
    171             snwice_mass_b(ji,jj) = snwice_mass(ji,jj)       ! save mass from the previous ice time step 
    172             !                                               ! new mass per unit area 
    173             snwice_mass  (ji,jj) = tmask(ji,jj,1) * ( rhos * vt_s(ji,jj) + rhoi * vt_i(ji,jj)  )  
    174             !                                               ! time evolution of snow+ice mass 
    175             snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_rdtice 
    176              
    177          END DO 
    178       END DO 
     115      DO_2D_11_11 
     116 
     117         ! Solar heat flux reaching the ocean = zqsr (W.m-2)  
     118         !--------------------------------------------------- 
     119         zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 
     120 
     121         ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2)  
     122         !--------------------------------------------------- 
     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 
     131         ! New qsr and qns used to compute the oceanic heat flux at the next time step 
     132         !---------------------------------------------------------------------------- 
     133         qsr(ji,jj) = zqsr                                       
     134         qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr               
     135 
     136         ! Mass flux at the atm. surface        
     137         !----------------------------------- 
     138         wfx_sub(ji,jj) = wfx_snw_sub(ji,jj) + wfx_ice_sub(ji,jj) 
     139 
     140         ! Mass flux at the ocean surface       
     141         !------------------------------------ 
     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 
     151         wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
     152            &           + 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 
     155         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 
     161 
     162         ! Salt flux at the ocean surface       
     163         !------------------------------------------ 
     164         sfx(ji,jj) = sfx_bog(ji,jj) + sfx_bom(ji,jj) + sfx_sum(ji,jj) + sfx_sni(ji,jj) + sfx_opw(ji,jj)   & 
     165            &       + sfx_res(ji,jj) + sfx_dyn(ji,jj) + sfx_bri(ji,jj) + sfx_sub(ji,jj) + sfx_lam(ji,jj) 
     166          
     167         ! Mass of snow and ice per unit area    
     168         !---------------------------------------- 
     169         snwice_mass_b(ji,jj) = snwice_mass(ji,jj)       ! save mass from the previous ice time step 
     170         !                                               ! new mass per unit area 
     171         snwice_mass  (ji,jj) = tmask(ji,jj,1) * ( rhos * vt_s(ji,jj) + rhoi * vt_i(ji,jj)  )  
     172         !                                               ! time evolution of snow+ice mass 
     173         snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_rdtice 
     174          
     175      END_2D 
    179176 
    180177      ! Storing the transmitted variables 
     
    286283#endif 
    287284      IF( ln_icectl                      )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    288       IF( ln_ctl                         )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
     285      IF( sn_cfctl%l_prtctl              )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    289286      IF( ln_timing                      )   CALL timing_stop   ('ice_update')                                      ! timing 
    290287      ! 
     
    335332      ! 
    336333      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !==  Ice time-step only  ==!   (i.e. surface module time-step) 
    337          DO jj = 2, jpjm1                             !* update the modulus of stress at ocean surface (T-point) 
    338             DO ji = fs_2, fs_jpim1 
    339                !                                               ! 2*(U_ice-U_oce) at T-point 
    340                zu_t = u_ice(ji,jj) + u_ice(ji-1,jj) - u_oce(ji,jj) - u_oce(ji-1,jj)    
    341                zv_t = v_ice(ji,jj) + v_ice(ji,jj-1) - v_oce(ji,jj) - v_oce(ji,jj-1)  
    342                !                                              ! |U_ice-U_oce|^2 
    343                zmodt =  0.25_wp * (  zu_t * zu_t + zv_t * zv_t  ) 
    344                !                                               ! update the ocean stress modulus 
    345                taum(ji,jj) = ( 1._wp - at_i(ji,jj) ) * taum(ji,jj) + at_i(ji,jj) * zrhoco * zmodt 
    346                tmod_io(ji,jj) = zrhoco * SQRT( zmodt )          ! rhoco * |U_ice-U_oce| at T-point 
    347             END DO 
    348          END DO 
     334         DO_2D_00_00 
     335            !                                               ! 2*(U_ice-U_oce) at T-point 
     336            zu_t = u_ice(ji,jj) + u_ice(ji-1,jj) - u_oce(ji,jj) - u_oce(ji-1,jj)    
     337            zv_t = v_ice(ji,jj) + v_ice(ji,jj-1) - v_oce(ji,jj) - v_oce(ji,jj-1)  
     338            !                                              ! |U_ice-U_oce|^2 
     339            zmodt =  0.25_wp * (  zu_t * zu_t + zv_t * zv_t  ) 
     340            !                                               ! update the ocean stress modulus 
     341            taum(ji,jj) = ( 1._wp - at_i(ji,jj) ) * taum(ji,jj) + at_i(ji,jj) * zrhoco * zmodt 
     342            tmod_io(ji,jj) = zrhoco * SQRT( zmodt )          ! rhoco * |U_ice-U_oce| at T-point 
     343         END_2D 
    349344         CALL lbc_lnk_multi( 'iceupdate', taum, 'T', 1., tmod_io, 'T', 1. ) 
    350345         ! 
     
    356351      !                                      !==  every ocean time-step  ==! 
    357352      ! 
    358       DO jj = 2, jpjm1                                !* update the stress WITHOUT an ice-ocean rotation angle 
    359          DO ji = fs_2, fs_jpim1   ! Vect. Opt.    
    360             ! ice area at u and v-points  
    361             zat_u  = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji+1,jj    ) * tmask(ji+1,jj  ,1) )  & 
    362                &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji+1,jj  ,1) ) 
    363             zat_v  = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji  ,jj+1  ) * tmask(ji  ,jj+1,1) )  & 
    364                &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji  ,jj+1,1) ) 
    365             !                                                   ! 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) ) 
    368             !                                                   ! stresses at the ocean surface 
    369             utau(ji,jj) = ( 1._wp - zat_u ) * utau_oce(ji,jj) + zat_u * zutau_ice 
    370             vtau(ji,jj) = ( 1._wp - zat_v ) * vtau_oce(ji,jj) + zat_v * zvtau_ice 
    371          END DO 
    372       END DO 
     353      DO_2D_00_00 
     354         ! ice area at u and v-points  
     355         zat_u  = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji+1,jj    ) * tmask(ji+1,jj  ,1) )  & 
     356            &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji+1,jj  ,1) ) 
     357         zat_v  = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji  ,jj+1  ) * tmask(ji  ,jj+1,1) )  & 
     358            &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji  ,jj+1,1) ) 
     359         !                                                   ! linearized quadratic drag formulation 
     360         zutau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji+1,jj) ) * ( u_ice(ji,jj) - pu_oce(ji,jj) ) 
     361         zvtau_ice   = 0.5_wp * ( tmod_io(ji,jj) + tmod_io(ji,jj+1) ) * ( v_ice(ji,jj) - pv_oce(ji,jj) ) 
     362         !                                                   ! stresses at the ocean surface 
     363         utau(ji,jj) = ( 1._wp - zat_u ) * utau_oce(ji,jj) + zat_u * zutau_ice 
     364         vtau(ji,jj) = ( 1._wp - zat_v ) * vtau_oce(ji,jj) + zat_v * zvtau_ice 
     365      END_2D 
    373366      CALL lbc_lnk_multi( 'iceupdate', utau, 'U', -1., vtau, 'V', -1. )   ! lateral boundary condition 
    374367      ! 
Note: See TracChangeset for help on using the changeset viewer.