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

Ignore:
Timestamp:
2017-07-21T17:59:19+02:00 (7 years ago)
Author:
clem
Message:

correct a bug introduced at r8327 => repro/restart + simplify again

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

Legend:

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

    r8341 r8360  
    441441   !! * Old values of global variables 
    442442   !!-------------------------------------------------------------------------- 
    443    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b               !: snow and ice volumes 
    444    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b     !: 
    445    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                      !: snow heat content 
    446    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                      !: ice temperatures 
    447    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b           !: ice velocity 
    448    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                     !: ice concentration (total) 
     443   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, ht_s_b, ht_i_b  !: snow and ice volumes/thickness 
     444   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b        !: 
     445   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                         !: snow heat content 
     446   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                         !: ice temperatures 
     447   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b              !: ice velocity 
     448   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                        !: ice concentration (total) 
    449449             
    450450   !!-------------------------------------------------------------------------- 
     
    597597      ! * Old values of global variables 
    598598      ii = ii + 1 
    599       ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , e_s_b(jpi,jpj,nlay_s,jpl) ,     & 
    600          &      a_i_b  (jpi,jpj,jpl) , smv_i_b(jpi,jpj,jpl) , e_i_b(jpi,jpj,nlay_i,jpl) ,     & 
    601          &      oa_i_b (jpi,jpj,jpl)                                                    , STAT=ierr(ii) ) 
     599      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , ht_s_b(jpi,jpj,jpl)        , ht_i_b(jpi,jpj,jpl)        ,   & 
     600         &      a_i_b  (jpi,jpj,jpl) , smv_i_b(jpi,jpj,jpl) , e_i_b (jpi,jpj,nlay_i,jpl) , e_s_b (jpi,jpj,nlay_s,jpl) ,   & 
     601         &      oa_i_b (jpi,jpj,jpl)                                                     , STAT=ierr(ii) ) 
    602602      ii = ii + 1 
    603603      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) ) 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8341 r8360  
    475475      !---------------------------------- 
    476476      ! 
    477       hi_max(:) = 0._wp 
    478       ! 
    479477      !==  h^(-alpha) function  ==! 
    480478      zalpha = 0.05_wp 
     
    485483         hi_max(jl) = ( znum / zden )**(1./zalpha) - 1 
    486484      END DO 
    487       ! 
    488485      ! 
    489486      DO jl = 1, jpl                ! mean thickness by category 
     
    584581      !! ** purpose :  store ice variables at "before" time step 
    585582      !!---------------------------------------------------------------------- 
    586       a_i_b  (:,:,:)   = a_i  (:,:,:)     ! ice area 
    587       e_i_b  (:,:,:,:) = e_i  (:,:,:,:)   ! ice thermal energy 
    588       v_i_b  (:,:,:)   = v_i  (:,:,:)     ! ice volume 
    589       v_s_b  (:,:,:)   = v_s  (:,:,:)     ! snow volume 
    590       e_s_b  (:,:,:,:) = e_s  (:,:,:,:)   ! snow thermal energy 
    591       smv_i_b(:,:,:)   = smv_i(:,:,:)     ! salt content 
    592       oa_i_b (:,:,:)   = oa_i (:,:,:)     ! areal age content 
    593       u_ice_b(:,:)     = u_ice(:,:) 
    594       v_ice_b(:,:)     = v_ice(:,:) 
    595       ! 
    596       at_i_b (:,:)     = SUM( a_i_b(:,:,:), dim=3 ) 
     583      INTEGER  ::   ji, jj, jl      ! dummy loop index 
     584      !!---------------------------------------------------------------------- 
     585      ! 
     586      DO jl = 1, jpl 
     587          
     588         DO jj = 1, jpj 
     589            DO ji = 1, jpi 
     590               a_i_b  (ji,jj,jl)   = a_i  (ji,jj,jl)     ! ice area 
     591               v_i_b  (ji,jj,jl)   = v_i  (ji,jj,jl)     ! ice volume 
     592               v_s_b  (ji,jj,jl)   = v_s  (ji,jj,jl)     ! snow volume 
     593               smv_i_b(ji,jj,jl)   = smv_i(ji,jj,jl)     ! salt content 
     594               oa_i_b (ji,jj,jl)   = oa_i (ji,jj,jl)     ! areal age content 
     595               e_s_b  (ji,jj,:,jl) = e_s  (ji,jj,:,jl)   ! snow thermal energy 
     596               e_i_b  (ji,jj,:,jl) = e_i  (ji,jj,:,jl)   ! ice thermal energy 
     597               !                                         ! ice thickness 
     598               rswitch = MAX( 0._wp , SIGN( 1._wp, a_i_b(ji,jj,jl) - epsi20 ) ) ! 0 if no ice and 1 if yes 
     599               ht_i_b(ji,jj,jl) = v_i_b (ji,jj,jl) / MAX( a_i_b(ji,jj,jl) , epsi20 ) * rswitch 
     600               ht_s_b(ji,jj,jl) = v_s_b (ji,jj,jl) / MAX( a_i_b(ji,jj,jl) , epsi20 ) * rswitch 
     601            END DO 
     602         END DO 
     603                   
     604      END DO 
     605       
     606      ! ice velocities & total concentration 
     607      DO jj = 1, jpj 
     608         DO ji = 1, jpi 
     609            at_i_b(ji,jj)  = SUM( a_i_b(ji,jj,:) ) 
     610            u_ice_b(ji,jj) = u_ice(ji,jj) 
     611            v_ice_b(ji,jj) = v_ice(ji,jj) 
     612         END DO 
     613      END DO 
    597614       
    598615   END SUBROUTINE ice_bef 
     
    606623      !!               of the time step 
    607624      !!---------------------------------------------------------------------- 
    608       sfx    (:,:) = 0._wp   ; 
    609       sfx_bri(:,:) = 0._wp   ;   sfx_lam(:,:) = 0._wp 
    610       sfx_sni(:,:) = 0._wp   ;   sfx_opw(:,:) = 0._wp 
    611       sfx_bog(:,:) = 0._wp   ;   sfx_dyn(:,:) = 0._wp 
    612       sfx_bom(:,:) = 0._wp   ;   sfx_sum(:,:) = 0._wp 
    613       sfx_res(:,:) = 0._wp   ;   sfx_sub(:,:) = 0._wp 
    614       ! 
    615       wfx_snw(:,:) = 0._wp   ;   wfx_ice(:,:) = 0._wp 
    616       wfx_sni(:,:) = 0._wp   ;   wfx_opw(:,:) = 0._wp 
    617       wfx_bog(:,:) = 0._wp   ;   wfx_dyn(:,:) = 0._wp 
    618       wfx_bom(:,:) = 0._wp   ;   wfx_sum(:,:) = 0._wp 
    619       wfx_res(:,:) = 0._wp   ;   wfx_sub(:,:) = 0._wp 
    620       wfx_spr(:,:) = 0._wp   ;   wfx_lam(:,:) = 0._wp   
    621       wfx_snw_dyn(:,:) = 0._wp ; wfx_snw_sum(:,:) = 0._wp 
    622       wfx_snw_sub(:,:) = 0._wp ; wfx_ice_sub(:,:) = 0._wp 
    623       wfx_snw_sni(:,:) = 0._wp  
    624       ! MV MP 2016 
    625       wfx_pnd(:,:) = 0._wp 
    626       ! END MV MP 2016 
    627        
    628       hfx_thd(:,:) = 0._wp   ; 
    629       hfx_snw(:,:) = 0._wp   ;   hfx_opw(:,:) = 0._wp 
    630       hfx_bog(:,:) = 0._wp   ;   hfx_dyn(:,:) = 0._wp 
    631       hfx_bom(:,:) = 0._wp   ;   hfx_sum(:,:) = 0._wp 
    632       hfx_res(:,:) = 0._wp   ;   hfx_sub(:,:) = 0._wp 
    633       hfx_spr(:,:) = 0._wp   ;   hfx_dif(:,:) = 0._wp 
    634       hfx_err(:,:) = 0._wp   ;   hfx_err_rem(:,:) = 0._wp 
    635       hfx_err_dif(:,:) = 0._wp 
    636       wfx_err_sub(:,:) = 0._wp 
    637       ! 
    638       afx_tot(:,:) = 0._wp   ; 
    639       afx_dyn(:,:) = 0._wp   ;   afx_thd(:,:) = 0._wp 
    640       ! 
    641       diag_heat(:,:) = 0._wp ;   diag_smvi(:,:) = 0._wp 
    642       diag_vice(:,:) = 0._wp ;   diag_vsnw(:,:) = 0._wp 
    643  
    644       ! SIMIP diagnostics 
    645       diag_dms_dyn(:,:)  = 0._wp ; diag_dmi_dyn(:,:)  = 0._wp 
    646       diag_fc_bo(:,:)    = 0._wp ; diag_fc_su(:,:)    = 0._wp 
    647  
    648       tau_icebfr(:,:) = 0._wp; ! landfast ice param only (clem: important to keep the init here) 
     625      INTEGER  ::   ji, jj      ! dummy loop index 
     626      !!---------------------------------------------------------------------- 
     627      DO jj = 1, jpj 
     628         DO ji = 1, jpi 
     629            sfx    (ji,jj) = 0._wp   ; 
     630            sfx_bri(ji,jj) = 0._wp   ;   sfx_lam(ji,jj) = 0._wp 
     631            sfx_sni(ji,jj) = 0._wp   ;   sfx_opw(ji,jj) = 0._wp 
     632            sfx_bog(ji,jj) = 0._wp   ;   sfx_dyn(ji,jj) = 0._wp 
     633            sfx_bom(ji,jj) = 0._wp   ;   sfx_sum(ji,jj) = 0._wp 
     634            sfx_res(ji,jj) = 0._wp   ;   sfx_sub(ji,jj) = 0._wp 
     635            ! 
     636            wfx_snw(ji,jj) = 0._wp   ;   wfx_ice(ji,jj) = 0._wp 
     637            wfx_sni(ji,jj) = 0._wp   ;   wfx_opw(ji,jj) = 0._wp 
     638            wfx_bog(ji,jj) = 0._wp   ;   wfx_dyn(ji,jj) = 0._wp 
     639            wfx_bom(ji,jj) = 0._wp   ;   wfx_sum(ji,jj) = 0._wp 
     640            wfx_res(ji,jj) = 0._wp   ;   wfx_sub(ji,jj) = 0._wp 
     641            wfx_spr(ji,jj) = 0._wp   ;   wfx_lam(ji,jj) = 0._wp   
     642            wfx_snw_dyn(ji,jj) = 0._wp ; wfx_snw_sum(ji,jj) = 0._wp 
     643            wfx_snw_sub(ji,jj) = 0._wp ; wfx_ice_sub(ji,jj) = 0._wp 
     644            wfx_snw_sni(ji,jj) = 0._wp  
     645            ! MV MP 2016 
     646            wfx_pnd(ji,jj) = 0._wp 
     647            ! END MV MP 2016 
     648             
     649            hfx_thd(ji,jj) = 0._wp   ; 
     650            hfx_snw(ji,jj) = 0._wp   ;   hfx_opw(ji,jj) = 0._wp 
     651            hfx_bog(ji,jj) = 0._wp   ;   hfx_dyn(ji,jj) = 0._wp 
     652            hfx_bom(ji,jj) = 0._wp   ;   hfx_sum(ji,jj) = 0._wp 
     653            hfx_res(ji,jj) = 0._wp   ;   hfx_sub(ji,jj) = 0._wp 
     654            hfx_spr(ji,jj) = 0._wp   ;   hfx_dif(ji,jj) = 0._wp 
     655            hfx_err(ji,jj) = 0._wp   ;   hfx_err_rem(ji,jj) = 0._wp 
     656            hfx_err_dif(ji,jj) = 0._wp 
     657            wfx_err_sub(ji,jj) = 0._wp 
     658            ! 
     659            afx_tot(ji,jj) = 0._wp   ; 
     660            afx_dyn(ji,jj) = 0._wp   ;   afx_thd(ji,jj) = 0._wp 
     661            ! 
     662            diag_heat(ji,jj) = 0._wp ;   diag_smvi(ji,jj) = 0._wp 
     663            diag_vice(ji,jj) = 0._wp ;   diag_vsnw(ji,jj) = 0._wp 
     664             
     665            ! SIMIP diagnostics 
     666            diag_dms_dyn(ji,jj)  = 0._wp ; diag_dmi_dyn(ji,jj)  = 0._wp 
     667            diag_fc_bo(ji,jj)    = 0._wp ; diag_fc_su(ji,jj)    = 0._wp 
     668             
     669            tau_icebfr(ji,jj) = 0._wp; ! landfast ice param only (clem: important to keep the init here) 
     670         END DO 
     671      END DO 
    649672       
    650673   END SUBROUTINE ice_diag0 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd_da.F90

    r8342 r8360  
    125125      END DO 
    126126 
    127       !------------------------------------------------------------! 
    128       ! --- Calculate reduction of total sea ice concentration --- ! 
    129       !------------------------------------------------------------! 
    130       zastar = 1._wp / ( 1._wp - (rn_dmin / zdmax)**(1._wp/rn_beta) ) 
    131  
    132       CALL tab_2d_1d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i  ) 
    133       CALL tab_2d_1d( nidx, idxice(1:nidx), t_bo_1d(1:nidx), t_bo  ) 
    134       CALL tab_2d_1d( nidx, idxice(1:nidx), sst_1d (1:nidx), sst_m ) 
    135  
    136       DO ji = 1, nidx    
    137          zdfloe = rn_dmin * ( zastar / ( zastar - at_i_1d(ji) ) )**rn_beta         ! Mean floe caliper diameter [m] 
    138          zperi  = at_i_1d(ji) * rpi / ( zcs * zdfloe )                             ! Mean perimeter of the floe = N*pi*D = (A/cs*D^2)*pi*D [m.m-2] 
    139          zwlat  = zm1 * ( MAX( 0._wp, sst_1d(ji) - ( t_bo_1d(ji) - rt0 ) ) )**zm2  ! Melt speed rate [m/s] 
    140           
    141          zda_tot(ji) = - MIN( zwlat * zperi * rdt_ice, at_i_1d(ji) )               ! sea ice concentration decrease 
    142       END DO 
    143        
    144       !---------------------------------------------------------------------------------------------! 
    145       ! --- Distribute reduction among ice categories and calculate associated ice-ocean fluxes --- ! 
    146       !---------------------------------------------------------------------------------------------! 
    147       DO jl = 1, jpl 
    148  
    149          CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d    (1:nidx), a_i(:,:,jl)  ) 
    150          CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d   (1:nidx), ht_i(:,:,jl) ) 
    151          CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d   (1:nidx), ht_s(:,:,jl) ) 
    152          CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d   (1:nidx), sm_i(:,:,jl) ) 
    153          CALL tab_2d_1d( nidx, idxice(1:nidx), sfx_lam_1d(1:nidx), sfx_lam      ) 
    154          CALL tab_2d_1d( nidx, idxice(1:nidx), hfx_thd_1d(1:nidx), hfx_thd      ) 
    155          CALL tab_2d_1d( nidx, idxice(1:nidx), wfx_lam_1d(1:nidx), wfx_lam      ) 
    156          DO jk = 1, nlay_i 
    157             CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl) ) 
     127      IF( nidx > 0 ) THEN 
     128         !------------------------------------------------------------! 
     129         ! --- Calculate reduction of total sea ice concentration --- ! 
     130         !------------------------------------------------------------! 
     131         CALL tab_2d_1d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i  ) 
     132         CALL tab_2d_1d( nidx, idxice(1:nidx), t_bo_1d(1:nidx), t_bo  ) 
     133         CALL tab_2d_1d( nidx, idxice(1:nidx), sst_1d (1:nidx), sst_m ) 
     134          
     135         zastar = 1._wp / ( 1._wp - (rn_dmin / zdmax)**(1._wp/rn_beta) ) 
     136         DO ji = 1, nidx    
     137            zdfloe = rn_dmin * ( zastar / ( zastar - at_i_1d(ji) ) )**rn_beta         ! Mean floe caliper diameter [m] 
     138            zperi  = at_i_1d(ji) * rpi / ( zcs * zdfloe )                             ! Mean perimeter of the floe = N*pi*D = (A/cs*D^2)*pi*D [m.m-2] 
     139            zwlat  = zm1 * ( MAX( 0._wp, sst_1d(ji) - ( t_bo_1d(ji) - rt0 ) ) )**zm2  ! Melt speed rate [m/s] 
     140             
     141            zda_tot(ji) = - MIN( zwlat * zperi * rdt_ice, at_i_1d(ji) )               ! sea ice concentration decrease 
    158142         END DO 
    159          DO jk = 1, nlay_s 
    160             CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl) ) 
    161          END DO 
    162  
    163          DO ji = 1, nidx 
    164             IF( a_i_1d(ji) > epsi10 ) THEN 
     143          
     144         !---------------------------------------------------------------------------------------------! 
     145         ! --- Distribute reduction among ice categories and calculate associated ice-ocean fluxes --- ! 
     146         !---------------------------------------------------------------------------------------------! 
     147         CALL tab_2d_1d( nidx, idxice(1:nidx), sfx_lam_1d(1:nidx), sfx_lam ) 
     148         CALL tab_2d_1d( nidx, idxice(1:nidx), hfx_thd_1d(1:nidx), hfx_thd ) 
     149         CALL tab_2d_1d( nidx, idxice(1:nidx), wfx_lam_1d(1:nidx), wfx_lam ) 
     150          
     151         DO jl = 1, jpl 
     152             
     153            CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl)  ) 
     154            CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,jl) ) 
     155            CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,jl) ) 
     156            CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,jl) ) 
     157            DO jk = 1, nlay_i 
     158               CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl) ) 
     159            END DO 
     160            DO jk = 1, nlay_s 
     161               CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl) ) 
     162            END DO 
     163             
     164            DO ji = 1, nidx 
    165165               ! decrease of concentration for the category jl 
    166166               !    each category contributes to melting in proportion to its concentration 
     
    171171                
    172172               ! Contribution to heat flux into the ocean [W.m-2], (<0)   
    173                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  
     173               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zda_tot(ji) / at_i_1d(ji) * SUM( e_i_1d(ji,1:nlay_i) + e_s_1d(ji,1) ) * r1_rdtice  
    174174               
    175175               ! Contribution to mass flux 
     
    177177            
    178178               !! adjust e_i ??? 
    179                e_i_1d(ji,:) = e_i_1d(ji,:) * ( 1._wp + zda / a_i_1d(ji) ) 
    180                e_s_1d(ji,1) = e_s_1d(ji,1) * ( 1._wp + zda / a_i_1d(ji) ) 
     179               e_i_1d(ji,1:nlay_i) = e_i_1d(ji,1:nlay_i) * ( 1._wp + zda_tot(ji) / at_i_1d(ji) ) 
     180               e_s_1d(ji,1)        = e_s_1d(ji,1)        * ( 1._wp + zda_tot(ji) / at_i_1d(ji) ) 
    181181  
    182182               ! new concentration 
     
    187187                  ht_i_1d(ji) = 0._wp 
    188188                  ht_s_1d(ji) = 0._wp 
    189                ENDIF 
    190  
    191             ENDIF       
     189               ENDIF             
     190            END DO 
     191 
     192            CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d    (1:nidx), a_i (:,:,jl) ) 
     193            CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d   (1:nidx), ht_i(:,:,jl) ) 
     194            CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d   (1:nidx), ht_s(:,:,jl) ) 
     195            DO jk = 1, nlay_s 
     196               CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl) ) 
     197            END DO 
     198            DO jk = 1, nlay_i 
     199               CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl) ) 
     200            END DO 
    192201             
    193202         END DO 
    194  
    195 !! je pense qu'il faut ajuster e_i mais je ne sais pas comment 
    196          DO jk = 1, nlay_s 
    197             CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl) ) 
    198          END DO 
    199          DO jk = 1, nlay_i 
    200             CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl) ) 
    201          END DO 
    202           
    203          CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d    (1:nidx), a_i (:,:,jl) ) 
    204          CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d   (1:nidx), ht_i(:,:,jl) ) 
    205          CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d   (1:nidx), ht_s(:,:,jl) ) 
    206          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d(1:nidx), sfx_lam      ) 
    207          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d(1:nidx), hfx_thd      ) 
    208          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d(1:nidx), wfx_lam      ) 
    209  
    210       END DO 
    211              
     203          
     204         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d(1:nidx), sfx_lam ) 
     205         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d(1:nidx), hfx_thd ) 
     206         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d(1:nidx), wfx_lam ) 
     207          
     208      ENDIF 
    212209      ! 
    213210   END SUBROUTINE lim_thd_da 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limvar.F90

    r8342 r8360  
    441441      !!------------------------------------------------------------------- 
    442442      INTEGER  ::   ji, jk    ! dummy loop indices 
    443       INTEGER  ::   ii, ij    ! local integers 
    444443      REAL(wp) ::   zfac0, zfac1, zargtemp, zsal   ! local scalars 
    445444      REAL(wp) ::   zalpha, zswi0, zswi01, zs_zero              !   -      - 
     
    474473         DO jk = 1, nlay_i 
    475474            DO ji = 1, nidx 
    476                ii =  MOD( idxice(ji) - 1 , jpi ) + 1 
    477                ij =     ( idxice(ji) - 1 ) / jpi + 1 
    478475               ! zswi0 = 1 if sm_i le zsi0 and 0 otherwise 
    479476               zswi0  = MAX( 0._wp , SIGN( 1._wp  , zsi0 - sm_i_1d(ji) ) )  
     
    482479               ! if 2.sm_i GE sss_m then rswitch = 1 
    483480               ! this is to force a constant salinity profile in the Baltic Sea 
    484                rswitch = MAX( 0._wp , SIGN( 1._wp , 2._wp * sm_i_1d(ji) - sss_m(ii,ij) ) ) 
     481               rswitch = MAX( 0._wp , SIGN( 1._wp , 2._wp * sm_i_1d(ji) - sss_1d(ji) ) ) 
    485482               ! 
    486483               zalpha = (  zswi0 + zswi01 * ( sm_i_1d(ji) * zfac0 + zfac1 )  ) * ( 1._wp - rswitch ) 
     
    529526      REAL(wp) ::   zsal, zvi, zvs, zei, zes, zvp 
    530527      !!------------------------------------------------------------------- 
    531       at_i (:,:) = 0._wp 
    532       DO jl = 1, jpl 
    533          at_i(:,:) = at_i(:,:) + a_i(:,:,jl) 
    534       END DO 
    535  
    536528      DO jl = 1, jpl 
    537529 
     
    543535               DO ji = 1 , jpi 
    544536                  rswitch          = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi10 ) ) 
    545                   rswitch          = MAX( 0._wp , SIGN( 1._wp, at_i(ji,jj  ) - epsi10 ) ) * rswitch 
    546537                  rswitch          = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) - epsi10 ) ) * rswitch 
    547538                  rswitch          = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) * rswitch  & 
     
    559550            DO ji = 1 , jpi 
    560551               rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi10 ) ) 
    561                rswitch = MAX( 0._wp , SIGN( 1._wp, at_i(ji,jj  ) - epsi10 ) ) * rswitch 
    562552               rswitch = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) - epsi10 ) ) * rswitch 
    563553               rswitch = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) * rswitch  & 
     
    584574               oa_i (ji,jj,jl) = oa_i (ji,jj,jl) * rswitch 
    585575               smv_i(ji,jj,jl) = smv_i(ji,jj,jl) * rswitch 
     576 
     577               ht_i (ji,jj,jl) = ht_i (ji,jj,jl) * rswitch 
     578               ht_s (ji,jj,jl) = ht_s (ji,jj,jl) * rswitch 
    586579 
    587580               ! MV MP 2016 
Note: See TracChangeset for help on using the changeset viewer.