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 8341 for branches/2017/dev_r8183_ICEMODEL – NEMO

Ignore:
Timestamp:
2017-07-15T13:00:17+02:00 (7 years ago)
Author:
clem
Message:

correct the heat conservation (all fine except limthd_da for a reason I do not understand)

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r8325 r8341  
    310310 
    311311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1] 
     312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sni !: snow ice growth component of wfx_snw [kg.m-2.s-1] 
    312313   ! MV MP 2016 
    313314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: surface melt component of wfx_snw [kg.m-2.s-1] 
     
    526527 
    527528      ii = ii + 1 
    528       ALLOCATE( t_bo   (jpi,jpj) ,                                                                       & 
     529      ALLOCATE( t_bo   (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                & 
    529530         &      wfx_snw(jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  & 
    530531         &      wfx_ice(jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  & 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8331 r8341  
    621621      wfx_snw_dyn(:,:) = 0._wp ; wfx_snw_sum(:,:) = 0._wp 
    622622      wfx_snw_sub(:,:) = 0._wp ; wfx_ice_sub(:,:) = 0._wp 
    623  
     623      wfx_snw_sni(:,:) = 0._wp  
    624624      ! MV MP 2016 
    625       wfx_pnd(:,:) = 0._wp   ;   wfx_snw_sum(:,:) = 0._wp 
     625      wfx_pnd(:,:) = 0._wp 
    626626      ! END MV MP 2016 
    627627       
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90

    r7646 r8341  
    188188 
    189189         ! water flux 
    190          zfw_b  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +               & 
    191             &                  wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) + wfx_lam(:,:)  & 
    192             &                ) *  e1e2t(:,:) * tmask(:,:,1) * zconv ) 
     190         zfw_b  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     & 
     191            &                  wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  & 
     192            &                  wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        & 
     193            &                ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 
    193194 
    194195         ! heat flux 
     
    213214 
    214215         ! water flux 
    215          zfw  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +                & 
    216             &                wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) + wfx_lam(:,:)   & 
     216         zfw  = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:)     + wfx_sum(:,:)     + wfx_sni(:,:)     +                     & 
     217            &                wfx_opw(:,:) + wfx_res(:,:)     + wfx_dyn(:,:)     + wfx_lam(:,:)     + wfx_ice_sub(:,:) +  & 
     218            &                wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:)        & 
    217219            &              ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfw_b 
    218220 
     
    229231            &                    * e1e2t * tmask(:,:,1) * zconv ) - zsmv_b ) * r1_rdtice + zfs ) * rday 
    230232 
    231          zei  =   glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  & 
     233         zei  = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +  & 
    232234            &                 SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )    & 
    233             &                ) * e1e2t * tmask(:,:,1) * zconv ) * r1_rdtice - zei_b * r1_rdtice + zft 
     235            &                ) * e1e2t * tmask(:,:,1) * zconv ) - zei_b ) * r1_rdtice + zft 
    234236 
    235237         ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limitd_me.F90

    r8321 r8341  
    668668 
    669669            wfx_snw_dyn(ji,jj)  =   wfx_snw_dyn(ji,jj) + zwfx_snw 
    670             wfx_snw(ji,jj)      =   wfx_snw(ji,jj)     + zwfx_snw 
    671670 
    672671            hfx_dyn(ji,jj) = hfx_dyn(ji,jj) + ( - esrdg(ij) * ( 1._wp - rn_fsnowrdg )         &  
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r8324 r8341  
    163163            qns(ji,jj) = hfx_out(ji,jj) - zqsr               
    164164 
    165             !------------------------------------------! 
    166             !      mass flux at the ocean surface      ! 
    167             !------------------------------------------! 
     165            ! Mass flux at the atm. surface        
     166            !----------------------------------- 
     167            wfx_sub(ji,jj) = wfx_snw_sub(ji,jj) + wfx_ice_sub(ji,jj) 
     168 
     169            ! Mass flux at the ocean surface       
     170            !------------------------------------ 
    168171            !  case of realistic freshwater flux (Tartinville et al., 2001) (presently ACTIVATED) 
    169172            !  -------------------------------------------------------------------------------------  
     
    178181                           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj)  
    179182 
    180             IF ( ln_pnd_fw ) & 
    181                wfx_ice(ji,jj) = wfx_ice(ji,jj) + wfx_pnd(ji,jj) 
     183            IF ( ln_pnd_fw )   wfx_ice(ji,jj) = wfx_ice(ji,jj) + wfx_pnd(ji,jj) 
    182184 
    183185            ! add the snow melt water to snow mass flux to the ocean 
    184             wfx_snw(ji,jj) = wfx_snw(ji,jj) + wfx_snw_sum(ji,jj)  
     186            wfx_snw(ji,jj) = wfx_snw_sni(ji,jj) + wfx_snw_dyn(ji,jj) + wfx_snw_sum(ji,jj) 
    185187 
    186188            ! mass flux at the ocean/ice interface 
    187189            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 
    188190            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) 
     191 
     192 
     193            ! Salt flux at the ocean surface       
     194            !------------------------------------------ 
     195            sfx(ji,jj) = sfx_bog(ji,jj) + sfx_bom(ji,jj) + sfx_sum(ji,jj) + sfx_sni(ji,jj) + sfx_opw(ji,jj)   & 
     196               &       + sfx_res(ji,jj) + sfx_dyn(ji,jj) + sfx_bri(ji,jj) + sfx_sub(ji,jj) + sfx_lam(ji,jj) 
     197             
     198            ! Mass of snow and ice per unit area    
     199            !---------------------------------------- 
     200            ! save mass from the previous ice time step 
     201            snwice_mass_b(ji,jj) = snwice_mass(ji,jj)                   
     202            ! new mass per unit area 
     203            snwice_mass  (ji,jj) = tmask(ji,jj,1) * ( rhosn * vt_s(ji,jj) + rhoic * vt_i(ji,jj)  )  
     204            ! time evolution of snow+ice mass 
     205            snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_rdtice 
     206             
    189207         END DO 
    190208      END DO 
    191  
    192       !------------------------------------------! 
    193       !      salt flux at the ocean surface      ! 
    194       !------------------------------------------! 
    195       sfx(:,:) = sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + sfx_opw(:,:)   & 
    196          &     + sfx_res(:,:) + sfx_dyn(:,:) + sfx_bri(:,:) + sfx_sub(:,:) + sfx_lam(:,:) 
    197  
    198       !----------------------------------------! 
    199       !   mass of snow and ice per unit area   ! 
    200       !----------------------------------------! 
    201       ! save mass from the previous ice time step 
    202       snwice_mass_b(:,:) = snwice_mass(:,:)                   
    203       ! new mass per unit area 
    204       snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
    205       ! time evolution of snow+ice mass 
    206       snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) * r1_rdtice 
    207209 
    208210      !-----------------------------------------------! 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd.F90

    r8332 r8341  
    279279         ENDIF 
    280280         ! 
    281       END DO !jl 
    282  
    283       IF( ln_limdA)           CALL lim_thd_da                                ! --- lateral melting --- ! 
    284  
    285       at_i(:,:)    = SUM( a_i(:,:,:), dim=3 ) 
     281      END DO 
     282      at_i(:,:) = SUM( a_i(:,:,:), dim=3 ) 
    286283 
    287284      ! Change thickness to volume 
     
    289286      v_s(:,:,:)   = ht_s(:,:,:) * a_i(:,:,:) 
    290287      smv_i(:,:,:) = sm_i(:,:,:) * v_i(:,:,:) 
     288      IF( ln_limdiachk ) CALL lim_cons_hsm(1, 'limthd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
     289 
     290      IF( ln_limdiachk ) CALL lim_cons_hsm(0, 'limitd_thd_da', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
     291      IF( ln_limdA)           CALL lim_thd_da                                ! --- lateral melting --- ! 
     292 
     293      ! Change thickness to volume 
     294      at_i(:,:)    = SUM( a_i(:,:,:), dim=3 ) 
     295      v_i(:,:,:)   = ht_i(:,:,:) * a_i(:,:,:) 
     296      v_s(:,:,:)   = ht_s(:,:,:) * a_i(:,:,:) 
     297      smv_i(:,:,:) = sm_i(:,:,:) * v_i(:,:,:) 
     298      IF( ln_limdiachk ) CALL lim_cons_hsm(1, 'limitd_thd_da', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
    291299 
    292300      ! update ice age (in case a_i changed, i.e. becomes 0 or lateral melting in monocat) 
     
    305313      IF( ln_limctl )    CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ' )   ! control print 
    306314      ! 
    307       IF( ln_limdiachk ) CALL lim_cons_hsm(1, 'limthd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
    308315 
    309316      !------------------------------------------------! 
     
    454461         CALL tab_2d_1d( nidx, fhld_1d    (1:nidx), fhld            , jpi, jpj, idxice(1:nidx) ) 
    455462         ! 
    456          CALL tab_2d_1d( nidx, wfx_snw_1d (1:nidx), wfx_snw         , jpi, jpj, idxice(1:nidx) ) 
     463         CALL tab_2d_1d( nidx, wfx_snw_sni_1d(1:nidx), wfx_snw_sni  , jpi, jpj, idxice(1:nidx) ) 
    457464         CALL tab_2d_1d( nidx, wfx_snw_sum_1d(1:nidx), wfx_snw_sum  , jpi, jpj, idxice(1:nidx) ) 
    458465         CALL tab_2d_1d( nidx, wfx_sub_1d (1:nidx), wfx_sub         , jpi, jpj, idxice(1:nidx) ) 
     
    516523         END DO 
    517524         ! 
    518          CALL tab_1d_2d( nidx, wfx_snw       , idxice, wfx_snw_1d(1:nidx)   , jpi, jpj ) 
     525         CALL tab_1d_2d( nidx, wfx_snw_sni   , idxice, wfx_snw_sni_1d(1:nidx), jpi, jpj ) 
    519526         CALL tab_1d_2d( nidx, wfx_snw_sum   , idxice, wfx_snw_sum_1d(1:nidx),jpi, jpj ) 
    520527         CALL tab_1d_2d( nidx, wfx_sub       , idxice, wfx_sub_1d(1:nidx)   , jpi, jpj ) 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd_da.F90

    r8332 r8341  
    102102      INTEGER             ::   ji, jj, jk, jl     ! dummy loop indices 
    103103      INTEGER             ::   nidx 
     104      REAL(wp) ::   ztmelts             ! local scalar 
     105      REAL(wp) ::   zEi          ! specific enthalpy of sea ice (J/kg) 
     106      REAL(wp) ::   zEw          ! specific enthalpy of exchanged water (J/kg) 
     107      REAL(wp) ::   zdE          ! specific enthalpy difference (J/kg) 
    104108      REAL(wp)            ::   zastar, zdfloe, zperi, zwlat, zda 
    105109      REAL(wp), PARAMETER ::   zdmax = 300._wp 
     
    130134      CALL tab_2d_1d( nidx, t_bo_1d(1:nidx), t_bo , jpi, jpj, idxice(1:nidx) ) 
    131135      CALL tab_2d_1d( nidx, sst_1d (1:nidx), sst_m, jpi, jpj, idxice(1:nidx) ) 
     136 
    132137      DO ji = 1, nidx    
    133138         zdfloe = rn_dmin * ( zastar / ( zastar - at_i_1d(ji) ) )**rn_beta         ! Mean floe caliper diameter [m] 
     
    142147      !---------------------------------------------------------------------------------------------! 
    143148      DO jl = 1, jpl 
     149 
    144150         CALL tab_2d_1d( nidx, a_i_1d    (1:nidx), a_i(:,:,jl) , jpi, jpj, idxice(1:nidx) ) 
    145151         CALL tab_2d_1d( nidx, ht_i_1d   (1:nidx), ht_i(:,:,jl), jpi, jpj, idxice(1:nidx) ) 
     152         CALL tab_2d_1d( nidx, ht_s_1d   (1:nidx), ht_s(:,:,jl), jpi, jpj, idxice(1:nidx) ) 
    146153         CALL tab_2d_1d( nidx, sm_i_1d   (1:nidx), sm_i(:,:,jl), jpi, jpj, idxice(1:nidx) ) 
    147154         CALL tab_2d_1d( nidx, sfx_lam_1d(1:nidx), sfx_lam     , jpi, jpj, idxice(1:nidx) ) 
     
    149156         CALL tab_2d_1d( nidx, wfx_lam_1d(1:nidx), wfx_lam     , jpi, jpj, idxice(1:nidx) ) 
    150157         DO jk = 1, nlay_i 
    151             CALL tab_2d_1d( nidx, e_i_1d(1:nidx,jk), e_i(:,:,jk,jl)  , jpi, jpj, idxice(1:nidx) ) 
     158            CALL tab_2d_1d( nidx, e_i_1d(1:nidx,jk), e_i(:,:,jk,jl), jpi, jpj, idxice(1:nidx) ) 
    152159         END DO 
    153160         DO jk = 1, nlay_s 
    154             CALL tab_2d_1d( nidx, e_s_1d(1:nidx,jk), e_s(:,:,jk,jl)  , jpi, jpj, idxice(1:nidx) ) 
     161            CALL tab_2d_1d( nidx, e_s_1d(1:nidx,jk), e_s(:,:,jk,jl), jpi, jpj, idxice(1:nidx) ) 
    155162         END DO 
    156163 
    157164         DO ji = 1, nidx 
    158             ! decrease of concentration for the category jl 
    159             !    each category contributes to melting in proportion to its concentration 
    160             zda     = zda_tot(ji) * a_i_1d(ji) / at_i_1d(ji) 
     165            IF( a_i_1d(ji) > epsi10 ) THEN 
     166               ! decrease of concentration for the category jl 
     167               !    each category contributes to melting in proportion to its concentration 
     168               zda = zda_tot(ji) * a_i_1d(ji) / at_i_1d(ji) 
     169                
     170               ! Contribution to salt flux 
     171               sfx_lam_1d(ji) = sfx_lam_1d(ji) - rhoic *  ht_i_1d(ji) * zda * sm_i_1d(ji) * r1_rdtice 
     172                
     173               ! Contribution to heat flux into the ocean [W.m-2], (<0)   
     174               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zda / a_i_1d(ji) * SUM( e_i_1d(ji,:) + e_s_1d(ji,1) ) * r1_rdtice  
     175               
     176               ! Contribution to mass flux 
     177               wfx_lam_1d(ji) =  wfx_lam_1d(ji) - zda * r1_rdtice * ( rhoic * ht_i_1d(ji) + rhosn * ht_s_1d(ji) ) 
     178            
     179               !! adjust e_i ??? 
     180               e_i_1d(ji,:) = e_i_1d(ji,:) * ( 1._wp + zda / a_i_1d(ji) ) 
     181               e_s_1d(ji,1) = e_s_1d(ji,1) * ( 1._wp + zda / a_i_1d(ji) ) 
     182  
     183               ! new concentration 
     184               a_i_1d(ji) = a_i_1d(ji) + zda 
     185 
     186               ! ensure that ht_i = 0 where a_i = 0 
     187               IF( a_i_1d(ji) == 0._wp ) THEN 
     188                  ht_i_1d(ji) = 0._wp 
     189                  ht_s_1d(ji) = 0._wp 
     190               ENDIF 
     191 
     192            ENDIF       
    161193             
    162             ! Contribution to salt flux 
    163             sfx_lam_1d(ji) = sfx_lam_1d(ji) - rhoic *  ht_i_1d(ji) * zda * sm_i_1d(ji) * r1_rdtice 
    164              
    165             ! Contribution to heat flux into the ocean [W.m-2], <0   
    166             !clemX               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zda * r1_rdtice * ( ht_i_1d(ji) * SUM( e_i_1d(ji,:) ) * r1_nlay_i  & 
    167             !                  &                                                     + ht_s_1d(ji) *      e_s_1d(ji,1)   * r1_nlay_s ) 
    168             hfx_thd_1d(ji) = hfx_thd_1d(ji) + zda_tot(ji) / at_i_1d(ji) * r1_rdtice * ( SUM( e_i_1d(ji,:) ) + e_s_1d(ji,1) ) 
    169              
    170             ! Contribution to mass flux 
    171             wfx_lam_1d(ji) =  wfx_lam_1d(ji) - zda * r1_rdtice * ( rhoic * ht_i_1d(ji) + rhosn * ht_s_1d(ji) ) 
    172              
    173             ! new concentration 
    174             a_i_1d(ji) = a_i_1d(ji) + zda 
    175  
    176             ! ensure that ht_i = 0 where a_i = 0 
    177             IF( a_i_1d(ji) == 0._wp )   ht_i_1d(ji) = 0._wp   
    178          END DO 
    179  
    180          CALL tab_1d_2d( nidx, a_i (:,:,jl), idxice, a_i_1d     (1:nidx), jpi, jpj ) 
    181          CALL tab_1d_2d( nidx, ht_i(:,:,jl), idxice, ht_i_1d    (1:nidx), jpi, jpj ) 
    182          CALL tab_1d_2d( nidx, sfx_lam     , idxice, sfx_lam_1d(1:nidx) , jpi, jpj ) 
    183          CALL tab_1d_2d( nidx, hfx_thd     , idxice, hfx_thd_1d(1:nidx) , jpi, jpj ) 
    184          CALL tab_1d_2d( nidx, wfx_lam     , idxice, wfx_lam_1d(1:nidx) , jpi, jpj ) 
     194         END DO 
     195 
     196!! je pense qu'il faut ajuster e_i mais je ne sais pas comment 
     197         DO jk = 1, nlay_s 
     198            CALL tab_1d_2d( nidx, e_s(:,:,jk,jl), idxice, e_s_1d(1:nidx,jk), jpi, jpj) 
     199         END DO 
     200         DO jk = 1, nlay_i 
     201            CALL tab_1d_2d( nidx, e_i(:,:,jk,jl), idxice, e_i_1d(1:nidx,jk), jpi, jpj) 
     202         END DO 
     203          
     204         CALL tab_1d_2d( nidx, a_i (:,:,jl), idxice, a_i_1d    (1:nidx), jpi, jpj ) 
     205         CALL tab_1d_2d( nidx, ht_i(:,:,jl), idxice, ht_i_1d   (1:nidx), jpi, jpj ) 
     206         CALL tab_1d_2d( nidx, ht_s(:,:,jl), idxice, ht_s_1d   (1:nidx), jpi, jpj ) 
     207         CALL tab_1d_2d( nidx, sfx_lam     , idxice, sfx_lam_1d(1:nidx), jpi, jpj ) 
     208         CALL tab_1d_2d( nidx, hfx_thd     , idxice, hfx_thd_1d(1:nidx), jpi, jpj ) 
     209         CALL tab_1d_2d( nidx, wfx_lam     , idxice, wfx_lam_1d(1:nidx), jpi, jpj ) 
    185210 
    186211      END DO 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd_dh.F90

    r8326 r8341  
    426426 
    427427      ! Iterative procedure 
    428       DO iter = 1, num_iter_max 
    429          DO ji = kideb, kiut 
    430             IF(  zf_tt(ji) < 0._wp  ) THEN 
     428      DO ji = kideb, kiut 
     429         IF(  zf_tt(ji) < 0._wp  ) THEN 
     430            DO iter = 1, num_iter_max 
    431431 
    432432               ! New bottom ice salinity (Cox & Weeks, JGR88 ) 
     
    460460               e_i_1d(ji,nlay_i+1) = -zEi * rhoic                        ! New ice energy of melting (J/m3, >0) 
    461461                
    462             ENDIF 
    463          END DO 
    464       END DO 
    465  
    466       ! Contribution to Energy and Salt Fluxes 
    467       DO ji = kideb, kiut 
    468          IF(  zf_tt(ji) < 0._wp  ) THEN 
    469             ! New ice growth 
    470                                      
     462            END DO 
     463            ! Contribution to Energy and Salt Fluxes                                     
    471464            zfmdt          = - rhoic * dh_i_bott(ji)             ! Mass flux x time step (kg/m2, < 0) 
    472465 
     
    498491            eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bott(ji) * e_i_1d(ji,nlay_i+1) 
    499492            h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bott(ji) 
     493 
    500494         ENDIF 
     495 
    501496      END DO 
    502497 
     
    611606      END DO 
    612607 
    613       ! Water fluxes 
    614       DO ji = kideb, kiut 
    615          wfx_sub_1d(ji) = wfx_snw_sub_1d(ji) + wfx_ice_sub_1d(ji) ! sum ice and snow sublimation contributions 
    616       END DO 
    617  
    618608      ! 
    619609      !------------------------------------------------------------------------------| 
     
    648638         ! Contribution to mass flux 
    649639         ! All snow is thrown in the ocean, and seawater is taken to replace the volume 
    650          wfx_sni_1d(ji) = wfx_sni_1d(ji) - a_i_1d(ji) * dh_snowice(ji) * rhoic * r1_rdtice 
    651          wfx_snw_1d(ji) = wfx_snw_1d(ji) + a_i_1d(ji) * dh_snowice(ji) * rhosn * r1_rdtice 
     640         wfx_sni_1d(ji)     = wfx_sni_1d(ji)    - a_i_1d(ji) * dh_snowice(ji) * rhoic * r1_rdtice 
     641         wfx_snw_sni_1d(ji) = wfx_snw_sni_1d(ji) + a_i_1d(ji) * dh_snowice(ji) * rhosn * r1_rdtice 
    652642 
    653643         ! update heat content (J.m-2) and layer thickness 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limvar.F90

    r8327 r8341  
    598598               sfx_res(ji,jj)  = sfx_res(ji,jj) - ( smv_i(ji,jj,jl) - zsal ) * rhoic * r1_rdtice 
    599599               wfx_res(ji,jj)  = wfx_res(ji,jj) - ( v_i(ji,jj,jl)   - zvi  ) * rhoic * r1_rdtice 
    600                wfx_snw(ji,jj)  = wfx_snw(ji,jj) - ( v_s(ji,jj,jl)   - zvs  ) * rhosn * r1_rdtice 
     600               wfx_res(ji,jj)  = wfx_res(ji,jj) - ( v_s(ji,jj,jl)   - zvs  ) * rhosn * r1_rdtice 
    601601               hfx_res(ji,jj)  = hfx_res(ji,jj) + ( e_s(ji,jj,1,jl) - zes ) * r1_rdtice ! W.m-2 <0 
    602602            END DO 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/thd_ice.F90

    r8327 r8341  
    5656   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_res_1d 
    5757 
    58    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_snw_1d  
     58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_snw_sni_1d  
    5959   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_snw_sum_1d 
    6060   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_sub_1d 
     
    158158      ii = ii + 1 
    159159      ALLOCATE( sprecip_1d (jpij) , at_i_1d    (jpij) ,                     & 
    160          &      fhtur_1d   (jpij) , wfx_snw_1d (jpij) , wfx_spr_1d (jpij) , wfx_snw_sum_1d(jpij) , & 
     160         &      fhtur_1d   (jpij) , wfx_snw_sni_1d (jpij) , wfx_spr_1d (jpij) , wfx_snw_sum_1d(jpij) , & 
    161161         &      fhld_1d    (jpij) , wfx_sub_1d (jpij) , wfx_bog_1d (jpij) , wfx_bom_1d(jpij) ,  & 
    162162         &      wfx_sum_1d(jpij)  , wfx_sni_1d (jpij) , wfx_opw_1d (jpij) , wfx_res_1d(jpij) ,  & 
Note: See TracChangeset for help on using the changeset viewer.