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 14789 for NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/ICE/iceupdate.F90 – NEMO

Ignore:
Timestamp:
2021-05-05T13:18:04+02:00 (3 years ago)
Author:
mcastril
Message:

[2021/HPC-11_mcastril_HPDAonline_DiagGPU] Update externals

Location:
NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
         5^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8^/vendors/PPR@HEAD            ext/PPR 
        89 
        910# SETTE 
        10 ^/utils/CI/sette@13559        sette 
         11^/utils/CI/sette@14244        sette 
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/ICE/iceupdate.F90

    r13643 r14789  
    6767      !!------------------------------------------------------------------- 
    6868      !!                ***  ROUTINE ice_update_flx *** 
    69       !!   
    70       !! ** Purpose :   Update the surface ocean boundary condition for heat  
     69      !! 
     70      !! ** Purpose :   Update the surface ocean boundary condition for heat 
    7171      !!                salt and mass over areas where sea-ice is non-zero 
    72       !!          
     72      !! 
    7373      !! ** Action  : - computes the heat and freshwater/salt fluxes 
    7474      !!                at the ice-ocean interface. 
    7575      !!              - Update the ocean sbc 
    76       !!      
    77       !! ** Outputs : - qsr     : sea heat flux:     solar  
     76      !! 
     77      !! ** Outputs : - qsr     : sea heat flux:     solar 
    7878      !!              - qns     : sea heat flux: non solar 
    79       !!              - emp     : freshwater budget: volume flux  
    80       !!              - sfx     : salt flux  
     79      !!              - emp     : freshwater budget: volume flux 
     80      !!              - sfx     : salt flux 
    8181      !!              - fr_i    : ice fraction 
    8282      !!              - tn_ice  : sea-ice surface temperature 
     
    9494      REAL(wp), DIMENSION(jpi,jpj) ::   z2d                  ! 2D workspace 
    9595      !!--------------------------------------------------------------------- 
    96       IF( ln_timing )   CALL timing_start('ice_update') 
     96      IF( ln_timing )   CALL timing_start('iceupdate') 
    9797 
    9898      IF( kt == nit000 .AND. lwp ) THEN 
     
    104104      ! Net heat flux on top of the ice-ocean (W.m-2) 
    105105      !---------------------------------------------- 
    106       qt_atm_oi(:,:) = qns_tot(:,:) + qsr_tot(:,:)  
     106      IF( ln_cndflx ) THEN   ! ice-atm interface = conduction (and melting) fluxes 
     107         qt_atm_oi(:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:) + & 
     108            &             SUM( a_i_b * ( qcn_ice + qml_ice + qtr_ice_top ), dim=3 ) + qemp_ice(:,:) 
     109      ELSE                   ! ice-atm interface = solar and non-solar fluxes 
     110         qt_atm_oi(:,:) = qns_tot(:,:) + qsr_tot(:,:)  
     111      ENDIF 
    107112 
    108113      ! --- case we bypass ice thermodynamics --- ! 
     
    114119         qevap_ice  (:,:,:) = 0._wp 
    115120      ENDIF 
    116        
     121 
    117122      DO_2D( 1, 1, 1, 1 ) 
    118123 
    119          ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2)  
     124         ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2) 
    120125         !--------------------------------------------------- 
    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)  
     126         IF( ln_cndflx ) THEN   ! ice-atm interface = conduction (and melting) fluxes 
     127            zqsr = ( 1._wp - at_i_b(ji,jj) ) * qsr_oce(ji,jj) + SUM( a_i_b (ji,jj,:) * qtr_ice_bot(ji,jj,:) ) 
     128         ELSE                   ! ice-atm interface = solar and non-solar fluxes 
     129            zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 
     130         ENDIF 
     131 
     132         ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2) 
    124133         !--------------------------------------------------- 
    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)                  
     134         IF( ln_icethd ) THEN 
     135            qt_oce_ai(ji,jj) = qt_atm_oi(ji,jj) - hfx_sum(ji,jj) - hfx_bom(ji,jj) - hfx_bog(ji,jj) & 
     136               &                                - hfx_dif(ji,jj) - hfx_opw(ji,jj) - hfx_snw(ji,jj) & 
     137               &                                + hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) & 
     138               &                                + hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) + hfx_spr(ji,jj) 
     139         ENDIF 
    129140          
    130141         ! New qsr and qns used to compute the oceanic heat flux at the next time step 
     
    144155         ! 
    145156         ! the non-solar is simply derived from the solar flux 
    146          qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr               
    147           
    148          ! Mass flux at the atm. surface        
     157         qns(ji,jj) = qt_oce_ai(ji,jj) - qsr(ji,jj) 
     158 
     159         ! Mass flux at the atm. surface 
    149160         !----------------------------------- 
    150161         wfx_sub(ji,jj) = wfx_snw_sub(ji,jj) + wfx_ice_sub(ji,jj) 
    151162 
    152          ! Mass flux at the ocean surface       
     163         ! Mass flux at the ocean surface 
    153164         !------------------------------------ 
    154165         ! ice-ocean  mass flux 
    155166         wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
    156             &           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) + wfx_pnd(ji,jj) 
    157           
     167            &           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) 
     168 
    158169         ! snw-ocean mass flux 
    159170         wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) 
    160           
     171 
    161172         ! 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 
    164  
    165          ! Salt flux at the ocean surface       
     173         fmmflx(ji,jj) =                - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_pnd(ji,jj) - wfx_err_sub(ji,jj)   ! ice-ocean mass flux saved at least for biogeochemical model 
     174         emp   (ji,jj) = emp_oce(ji,jj) - wfx_ice(ji,jj) - wfx_snw(ji,jj) - wfx_pnd(ji,jj) - wfx_err_sub(ji,jj)   ! atm-ocean + ice-ocean mass flux 
     175 
     176         ! Salt flux at the ocean surface 
    166177         !------------------------------------------ 
    167178         sfx(ji,jj) = sfx_bog(ji,jj) + sfx_bom(ji,jj) + sfx_sum(ji,jj) + sfx_sni(ji,jj) + sfx_opw(ji,jj)   & 
    168179            &       + sfx_res(ji,jj) + sfx_dyn(ji,jj) + sfx_bri(ji,jj) + sfx_sub(ji,jj) + sfx_lam(ji,jj) 
    169           
    170          ! Mass of snow and ice per unit area    
     180 
     181         ! Mass of snow and ice per unit area 
    171182         !---------------------------------------- 
    172183         snwice_mass_b(ji,jj) = snwice_mass(ji,jj)       ! save mass from the previous ice time step 
    173184         !                                               ! new mass per unit area 
    174          snwice_mass  (ji,jj) = tmask(ji,jj,1) * ( rhos * vt_s(ji,jj) + rhoi * vt_i(ji,jj)  )  
     185         snwice_mass  (ji,jj) = tmask(ji,jj,1) * ( rhos * vt_s(ji,jj) + rhoi * vt_i(ji,jj) + rhow * (vt_ip(ji,jj) + vt_il(ji,jj)) ) 
    175186         !                                               ! time evolution of snow+ice mass 
    176187         snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_Dt_ice 
    177           
     188 
    178189      END_2D 
    179190 
    180191      ! Storing the transmitted variables 
    181192      !---------------------------------- 
    182       fr_i  (:,:)   = at_i(:,:)             ! Sea-ice fraction             
    183       tn_ice(:,:,:) = t_su(:,:,:)           ! Ice surface temperature                       
     193      fr_i  (:,:)   = at_i(:,:)             ! Sea-ice fraction 
     194      tn_ice(:,:,:) = t_su(:,:,:)           ! Ice surface temperature 
    184195 
    185196      ! Snow/ice albedo (only if sent to coupler, useless in forced mode) 
     
    216227      CALL iom_put( 'vfxice'    , wfx_ice     )   ! mass flux from total ice growth/melt 
    217228      CALL iom_put( 'vfxbog'    , wfx_bog     )   ! mass flux from bottom growth 
    218       CALL iom_put( 'vfxbom'    , wfx_bom     )   ! mass flux from bottom melt  
    219       CALL iom_put( 'vfxsum'    , wfx_sum     )   ! mass flux from surface melt  
    220       CALL iom_put( 'vfxlam'    , wfx_lam     )   ! mass flux from lateral melt  
     229      CALL iom_put( 'vfxbom'    , wfx_bom     )   ! mass flux from bottom melt 
     230      CALL iom_put( 'vfxsum'    , wfx_sum     )   ! mass flux from surface melt 
     231      CALL iom_put( 'vfxlam'    , wfx_lam     )   ! mass flux from lateral melt 
    221232      CALL iom_put( 'vfxsni'    , wfx_sni     )   ! mass flux from snow-ice formation 
    222233      CALL iom_put( 'vfxopw'    , wfx_opw     )   ! mass flux from growth in open water 
    223234      CALL iom_put( 'vfxdyn'    , wfx_dyn     )   ! mass flux from dynamics (ridging) 
    224       CALL iom_put( 'vfxres'    , wfx_res     )   ! mass flux from undiagnosed processes  
     235      CALL iom_put( 'vfxres'    , wfx_res     )   ! mass flux from undiagnosed processes 
    225236      CALL iom_put( 'vfxpnd'    , wfx_pnd     )   ! mass flux from melt ponds 
    226237      CALL iom_put( 'vfxsub'    , wfx_ice_sub )   ! mass flux from ice sublimation (ice-atm.) 
    227       CALL iom_put( 'vfxsub_err', wfx_err_sub )   ! "excess" of sublimation sent to ocean       
    228  
    229       IF ( iom_use( 'vfxthin' ) ) THEN   ! mass flux from ice growth in open water + thin ice (<20cm) => comparable to observations   
     238      CALL iom_put( 'vfxsub_err', wfx_err_sub )   ! "excess" of sublimation sent to ocean 
     239 
     240      IF ( iom_use( 'vfxthin' ) ) THEN   ! mass flux from ice growth in open water + thin ice (<20cm) => comparable to observations 
    230241         WHERE( hm_i(:,:) < 0.2 .AND. hm_i(:,:) > 0. ) ; z2d = wfx_bog 
    231242         ELSEWHERE                                     ; z2d = 0._wp 
     
    237248      CALL iom_put( 'vfxsnw'     , wfx_snw     )   ! mass flux from total snow growth/melt 
    238249      CALL iom_put( 'vfxsnw_sum' , wfx_snw_sum )   ! mass flux from snow melt at the surface 
    239       CALL iom_put( 'vfxsnw_sni' , wfx_snw_sni )   ! mass flux from snow melt during snow-ice formation  
    240       CALL iom_put( 'vfxsnw_dyn' , wfx_snw_dyn )   ! mass flux from dynamics (ridging)  
    241       CALL iom_put( 'vfxsnw_sub' , wfx_snw_sub )   ! mass flux from snow sublimation (ice-atm.)  
     250      CALL iom_put( 'vfxsnw_sni' , wfx_snw_sni )   ! mass flux from snow melt during snow-ice formation 
     251      CALL iom_put( 'vfxsnw_dyn' , wfx_snw_dyn )   ! mass flux from dynamics (ridging) 
     252      CALL iom_put( 'vfxsnw_sub' , wfx_snw_sub )   ! mass flux from snow sublimation (ice-atm.) 
    242253      CALL iom_put( 'vfxsnw_pre' , wfx_spr     )   ! snow precip 
    243254 
     
    252263      IF( iom_use('qt_oce'     ) )   CALL iom_put( 'qt_oce'     ,      ( qsr_oce + qns_oce ) * ( 1._wp - at_i_b ) + qemp_oce ) 
    253264      IF( iom_use('qt_ice'     ) )   CALL iom_put( 'qt_ice'     , SUM( ( qns_ice + qsr_ice ) * a_i_b, dim=3 )     + qemp_ice ) 
    254       IF( iom_use('qt_oce_ai'  ) )   CALL iom_put( 'qt_oce_ai'  , qt_oce_ai * tmask(:,:,1)                                   )   ! total heat flux at the ocean   surface: interface oce-(ice+atm)  
    255       IF( iom_use('qt_atm_oi'  ) )   CALL iom_put( 'qt_atm_oi'  , qt_atm_oi * tmask(:,:,1)                                   )   ! total heat flux at the oce-ice surface: interface atm-(ice+oce)  
     265      IF( iom_use('qt_oce_ai'  ) )   CALL iom_put( 'qt_oce_ai'  , qt_oce_ai * tmask(:,:,1)                                   )   ! total heat flux at the ocean   surface: interface oce-(ice+atm) 
     266      IF( iom_use('qt_atm_oi'  ) )   CALL iom_put( 'qt_atm_oi'  , qt_atm_oi * tmask(:,:,1)                                   )   ! total heat flux at the oce-ice surface: interface atm-(ice+oce) 
    256267      IF( iom_use('qemp_oce'   ) )   CALL iom_put( 'qemp_oce'   , qemp_oce                                                   )   ! Downward Heat Flux from E-P over ocean 
    257268      IF( iom_use('qemp_ice'   ) )   CALL iom_put( 'qemp_ice'   , qemp_ice                                                   )   ! Downward Heat Flux from E-P over ice 
     
    259270      ! heat fluxes from ice transformations 
    260271      !                            ! hfxdhc = hfxbog + hfxbom + hfxsum + hfxopw + hfxdif + hfxsnw - ( hfxthd + hfxdyn + hfxres + hfxsub + hfxspr ) 
    261       CALL iom_put ('hfxbog'     , hfx_bog     )   ! heat flux used for ice bottom growth  
     272      CALL iom_put ('hfxbog'     , hfx_bog     )   ! heat flux used for ice bottom growth 
    262273      CALL iom_put ('hfxbom'     , hfx_bom     )   ! heat flux used for ice bottom melt 
    263274      CALL iom_put ('hfxsum'     , hfx_sum     )   ! heat flux used for ice surface melt 
    264275      CALL iom_put ('hfxopw'     , hfx_opw     )   ! heat flux used for ice formation in open water 
    265276      CALL iom_put ('hfxdif'     , hfx_dif     )   ! heat flux used for ice temperature change 
    266       CALL iom_put ('hfxsnw'     , hfx_snw     )   ! heat flux used for snow melt  
     277      CALL iom_put ('hfxsnw'     , hfx_snw     )   ! heat flux used for snow melt 
    267278      CALL iom_put ('hfxerr'     , hfx_err_dif )   ! heat flux error after heat diffusion 
    268279 
    269280      ! heat fluxes associated with mass exchange (freeze/melt/precip...) 
    270       CALL iom_put ('hfxthd'     , hfx_thd     )   !   
    271       CALL iom_put ('hfxdyn'     , hfx_dyn     )   !   
    272       CALL iom_put ('hfxres'     , hfx_res     )   !   
    273       CALL iom_put ('hfxsub'     , hfx_sub     )   !   
    274       CALL iom_put ('hfxspr'     , hfx_spr     )   ! Heat flux from snow precip heat content  
     281      CALL iom_put ('hfxthd'     , hfx_thd     )   ! 
     282      CALL iom_put ('hfxdyn'     , hfx_dyn     )   ! 
     283      CALL iom_put ('hfxres'     , hfx_res     )   ! 
     284      CALL iom_put ('hfxsub'     , hfx_sub     )   ! 
     285      CALL iom_put ('hfxspr'     , hfx_spr     )   ! Heat flux from snow precip heat content 
    275286 
    276287      ! other heat fluxes 
    277       IF( iom_use('hfxsensib'  ) )   CALL iom_put( 'hfxsensib'  ,     -qsb_ice_bot * at_i_b         )   ! Sensible oceanic heat flux 
     288      IF( iom_use('hfxsensib'  ) )   CALL iom_put( 'hfxsensib'  ,      qsb_ice_bot * at_i_b         )   ! Sensible oceanic heat flux 
    278289      IF( iom_use('hfxcndbot'  ) )   CALL iom_put( 'hfxcndbot'  , SUM( qcn_ice_bot * a_i_b, dim=3 ) )   ! Bottom conduction flux 
    279290      IF( iom_use('hfxcndtop'  ) )   CALL iom_put( 'hfxcndtop'  , SUM( qcn_ice_top * a_i_b, dim=3 ) )   ! Surface conduction flux 
     291      IF( iom_use('hfxmelt'    ) )   CALL iom_put( 'hfxmelt'    , SUM( qml_ice     * a_i_b, dim=3 ) )   ! Surface melt flux 
     292      IF( iom_use('hfxldmelt'  ) )   CALL iom_put( 'hfxldmelt'  ,      fhld        * at_i_b         )   ! Heat in lead for ice melting  
     293      IF( iom_use('hfxldgrow'  ) )   CALL iom_put( 'hfxldgrow'  ,      qlead       * r1_Dt_ice      )   ! Heat in lead for ice growth 
    280294 
    281295      ! controls 
     
    286300      IF( ln_icectl         )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    287301      IF( sn_cfctl%l_prtctl )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    288       IF( ln_timing         )   CALL timing_stop   ('ice_update')                                      ! timing 
     302      IF( ln_timing         )   CALL timing_stop   ('iceupdate')                                       ! timing 
    289303      ! 
    290304   END SUBROUTINE ice_update_flx 
     
    294308      !!------------------------------------------------------------------- 
    295309      !!                ***  ROUTINE ice_update_tau *** 
    296       !!   
     310      !! 
    297311      !! ** Purpose : Update the ocean surface stresses due to the ice 
    298       !!          
     312      !! 
    299313      !! ** Action  : * at each ice time step (every nn_fsbc time step): 
    300       !!                - compute the modulus of ice-ocean relative velocity  
     314      !!                - compute the modulus of ice-ocean relative velocity 
    301315      !!                  (*rho*Cd) at T-point (C-grid) or I-point (B-grid) 
    302316      !!                      tmod_io = rhoco * | U_ice-U_oce | 
    303317      !!                - update the modulus of stress at ocean surface 
    304318      !!                      taum = (1-a) * taum + a * tmod_io * | U_ice-U_oce | 
    305       !!              * at each ocean time step (every kt):  
     319      !!              * at each ocean time step (every kt): 
    306320      !!                  compute linearized ice-ocean stresses as 
    307321      !!                      Utau = tmod_io * | U_ice - pU_oce | 
     
    310324      !!    NB: - ice-ocean rotation angle no more allowed 
    311325      !!        - here we make an approximation: taum is only computed every ice time step 
    312       !!          This avoids mutiple average to pass from T -> U,V grids and next from U,V grids  
     326      !!          This avoids mutiple average to pass from T -> U,V grids and next from U,V grids 
    313327      !!          to T grid. taum is used in TKE and GLS, which should not be too sensitive to this approximaton... 
    314328      !! 
     
    324338      REAL(wp) ::   zflagi                          !   -      - 
    325339      !!--------------------------------------------------------------------- 
    326       IF( ln_timing )   CALL timing_start('ice_update_tau') 
     340      IF( ln_timing )   CALL timing_start('ice_update') 
    327341 
    328342      IF( kt == nit000 .AND. lwp ) THEN 
     
    337351         DO_2D( 0, 0, 0, 0 )                          !* update the modulus of stress at ocean surface (T-point) 
    338352            !                                               ! 2*(U_ice-U_oce) at T-point 
    339             zu_t = u_ice(ji,jj) + u_ice(ji-1,jj) - u_oce(ji,jj) - u_oce(ji-1,jj)    
    340             zv_t = v_ice(ji,jj) + v_ice(ji,jj-1) - v_oce(ji,jj) - v_oce(ji,jj-1)  
     353            zu_t = u_ice(ji,jj) + u_ice(ji-1,jj) - u_oce(ji,jj) - u_oce(ji-1,jj) 
     354            zv_t = v_ice(ji,jj) + v_ice(ji,jj-1) - v_oce(ji,jj) - v_oce(ji,jj-1) 
    341355            !                                              ! |U_ice-U_oce|^2 
    342356            zmodt =  0.25_wp * (  zu_t * zu_t + zv_t * zv_t  ) 
     
    345359            tmod_io(ji,jj) = zrhoco * SQRT( zmodt )          ! rhoco * |U_ice-U_oce| at T-point 
    346360         END_2D 
    347          CALL lbc_lnk_multi( 'iceupdate', taum, 'T', 1.0_wp, tmod_io, 'T', 1.0_wp ) 
     361         CALL lbc_lnk( 'iceupdate', taum, 'T', 1.0_wp, tmod_io, 'T', 1.0_wp ) 
    348362         ! 
    349363         utau_oce(:,:) = utau(:,:)                    !* save the air-ocean stresses at ice time-step 
     
    354368      !                                      !==  every ocean time-step  ==! 
    355369      IF ( ln_drgice_imp ) THEN 
    356          ! Save drag with right sign to update top drag in the ocean implicit friction  
    357          rCdU_ice(:,:) = -r1_rho0 * tmod_io(:,:) * at_i(:,:) * tmask(:,:,1)  
     370         ! Save drag with right sign to update top drag in the ocean implicit friction 
     371         rCdU_ice(:,:) = -r1_rho0 * tmod_io(:,:) * at_i(:,:) * tmask(:,:,1) 
    358372         zflagi = 0._wp 
    359373      ELSE 
     
    362376      ! 
    363377      DO_2D( 0, 0, 0, 0 )                             !* update the stress WITHOUT an ice-ocean rotation angle 
    364          ! ice area at u and v-points  
     378         ! ice area at u and v-points 
    365379         zat_u  = ( at_i(ji,jj) * tmask(ji,jj,1) + at_i (ji+1,jj    ) * tmask(ji+1,jj  ,1) )  & 
    366380            &     / MAX( 1.0_wp , tmask(ji,jj,1) + tmask(ji+1,jj  ,1) ) 
     
    374388         vtau(ji,jj) = ( 1._wp - zat_v ) * vtau_oce(ji,jj) + zat_v * zvtau_ice 
    375389      END_2D 
    376       CALL lbc_lnk_multi( 'iceupdate', utau, 'U', -1.0_wp, vtau, 'V', -1.0_wp )   ! lateral boundary condition 
    377       ! 
    378       IF( ln_timing )   CALL timing_stop('ice_update_tau') 
    379       !   
     390      CALL lbc_lnk( 'iceupdate', utau, 'U', -1.0_wp, vtau, 'V', -1.0_wp )   ! lateral boundary condition 
     391      ! 
     392      IF( ln_timing )   CALL timing_stop('ice_update') 
     393      ! 
    380394   END SUBROUTINE ice_update_tau 
    381395 
     
    384398      !!------------------------------------------------------------------- 
    385399      !!                  ***  ROUTINE ice_update_init  *** 
    386       !!              
     400      !! 
    387401      !! ** Purpose :   allocate ice-ocean stress fields and read restarts 
    388402      !!                containing the snow & ice mass 
     
    408422      !!--------------------------------------------------------------------- 
    409423      !!                   ***  ROUTINE rhg_evp_rst  *** 
    410       !!                      
     424      !! 
    411425      !! ** Purpose :   Read or write RHG file in restart file 
    412426      !! 
     
    456470   !!   Default option         Dummy module           NO SI3 sea-ice model 
    457471   !!---------------------------------------------------------------------- 
    458 #endif  
     472#endif 
    459473 
    460474   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.