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 13497 for NEMO/trunk/src/OCE/ZDF – NEMO

Ignore:
Timestamp:
2020-09-21T14:37:46+02:00 (4 years ago)
Author:
techene
Message:

re-introduce comments that have been erased by loops transformation see #2525

Location:
NEMO/trunk/src/OCE/ZDF
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/ZDF/zdfddm.F90

    r13295 r13497  
    9494!!gm                            and many acces in memory 
    9595          
    96          DO_2D( 1, 1, 1, 1 ) 
     96         DO_2D( 1, 1, 1, 1 )           !==  R=zrau = (alpha / beta) (dk[t] / dk[s])  ==! 
    9797            zrw =   ( gdepw(ji,jj,jk  ,Kmm) - gdept(ji,jj,jk,Kmm) )   & 
    9898!!gm please, use e3w at Kmm below  
     
    110110         END_2D 
    111111 
    112          DO_2D( 1, 1, 1, 1 ) 
     112         DO_2D( 1, 1, 1, 1 )           !==  indicators  ==! 
    113113            ! stability indicator: msks=1 if rn2>0; 0 elsewhere 
    114114            IF( rn2(ji,jj,jk) + 1.e-12  <= 0. ) THEN   ;   zmsks(ji,jj) = 0._wp 
  • NEMO/trunk/src/OCE/ZDF/zdfdrg.F90

    r13477 r13497  
    431431            l_log_not_linssh = .FALSE.    !- don't update Cd at each time step 
    432432            ! 
    433             DO_2D( 1, 1, 1, 1 ) 
     433            DO_2D( 1, 1, 1, 1 )              ! pCd0 = mask (and boosted) logarithmic drag coef. 
    434434               zzz =  0.5_wp * e3t_0(ji,jj,k_mk(ji,jj)) 
    435435               zcd = (  vkarmn / LOG( zzz / rn_z0 )  )**2 
  • NEMO/trunk/src/OCE/ZDF/zdfgls.F90

    r13472 r13497  
    179179       
    180180      ! Compute surface, top and bottom friction at T-points 
    181       DO_2D( 0, 0, 0, 0 ) 
     181      DO_2D( 0, 0, 0, 0 )          !==  surface ocean friction 
    182182         ustar2_surf(ji,jj) = r1_rho0 * taum(ji,jj) * tmask(ji,jj,1)   ! surface friction 
    183183      END_2D 
     
    185185      !!gm Rq we may add here r_ke0(_top/_bot) ?  ==>> think about that... 
    186186      !     
    187       IF( .NOT.ln_drg_OFF ) THEN   !== top/bottom friction   (explicit before friction) 
    188          DO_2D( 0, 0, 0, 0 )       ! bottom friction (explicit before friction) 
     187      IF( .NOT.ln_drg_OFF ) THEN     !== top/bottom friction   (explicit before friction) 
     188         DO_2D( 0, 0, 0, 0 )         ! bottom friction (explicit before friction) 
    189189            zmsku = ( 2._wp - umask(ji-1,jj,mbkt(ji,jj)) * umask(ji,jj,mbkt(ji,jj)) ) 
    190190            zmskv = ( 2._wp - vmask(ji,jj-1,mbkt(ji,jj)) * vmask(ji,jj,mbkt(ji,jj)) )     ! (CAUTION: CdU<0) 
     
    193193         END_2D 
    194194         IF( ln_isfcav ) THEN 
    195             DO_2D( 0, 0, 0, 0 )    ! top friction 
     195            DO_2D( 0, 0, 0, 0 )      ! top friction 
    196196               zmsku = ( 2. - umask(ji-1,jj,mikt(ji,jj)) * umask(ji,jj,mikt(ji,jj)) ) 
    197197               zmskv = ( 2. - vmask(ji,jj-1,mikt(ji,jj)) * vmask(ji,jj,mikt(ji,jj)) )     ! (CAUTION: CdU<0) 
     
    220220      zhsro(:,:) = ( (1._wp-zice_fra(:,:)) * zhsro(:,:) + zice_fra(:,:) * rn_hsri )*tmask(:,:,1)  + (1._wp - tmask(:,:,1))*rn_hsro 
    221221      ! 
    222       DO_3D( 1, 0, 1, 0, 2, jpkm1 ) 
     222      DO_3D( 1, 0, 1, 0, 2, jpkm1 )  !==  Compute dissipation rate  ==! 
    223223         eps(ji,jj,jk)  = rc03 * en(ji,jj,jk) * SQRT( en(ji,jj,jk) ) / hmxl_n(ji,jj,jk) 
    224224      END_3D 
     
    416416      ! ---------------------------------------------------------- 
    417417      ! 
    418       DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     418      DO_3D( 0, 0, 0, 0, 2, jpkm1 )                ! First recurrence : Dk = Dk - Lk * Uk-1 / Dk-1 
    419419         zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    420420      END_3D 
    421       DO_3D( 0, 0, 0, 0, 2, jpk ) 
     421      DO_3D( 0, 0, 0, 0, 2, jpk )                  ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    422422         zd_lw(ji,jj,jk) = en(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) * zd_lw(ji,jj,jk-1) 
    423423      END_3D 
    424       DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 ) 
     424      DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 )           ! thrid recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    425425         en(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * en(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    426426      END_3D 
     
    610610      ! ---------------- 
    611611      ! 
    612       DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     612      DO_3D( 0, 0, 0, 0, 2, jpkm1 )                ! First recurrence : Dk = Dk - Lk * Uk-1 / Dk-1 
    613613         zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    614614      END_3D 
    615       DO_3D( 0, 0, 0, 0, 2, jpk ) 
     615      DO_3D( 0, 0, 0, 0, 2, jpk )                  ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    616616         zd_lw(ji,jj,jk) = psi(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) * zd_lw(ji,jj,jk-1) 
    617617      END_3D 
    618       DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 ) 
     618      DO_3DS( 0, 0, 0, 0, jpk-1, 2, -1 )           ! Third recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    619619         psi(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * psi(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    620620      END_3D 
     
    652652      ! Limit dissipation rate under stable stratification 
    653653      ! -------------------------------------------------- 
    654       DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     654      DO_3D( 0, 0, 0, 0, 1, jpkm1 )   ! Note that this set boundary conditions on hmxl_n at the same time 
    655655         ! limitation 
    656656         eps   (ji,jj,jk)  = MAX( eps(ji,jj,jk), rn_epsmin ) 
     
    717717      ! default value, in case jpk > mbkt(ji,jj)+1. Not needed but avoid a bug when looking for undefined values (-fpe0) 
    718718      zstm(:,:,jpk) = 0.   
    719       DO_2D( 0, 0, 0, 0 ) 
     719      DO_2D( 0, 0, 0, 0 )             ! update bottom with good values 
    720720         zstm(ji,jj,mbkt(ji,jj)+1) = zstm(ji,jj,mbkt(ji,jj)) 
    721721      END_2D 
  • NEMO/trunk/src/OCE/ZDF/zdfiwm.F90

    r13417 r13497  
    164164      !                       !* Critical slope mixing: distribute energy over the time-varying ocean depth, 
    165165      !                                                 using an exponential decay from the seafloor. 
    166       DO_2D( 0, 0, 0, 0 ) 
     166      DO_2D( 0, 0, 0, 0 )             ! part independent of the level 
    167167         zhdep(ji,jj) = gdepw_0(ji,jj,mbkt(ji,jj)+1)       ! depth of the ocean 
    168168         zfact(ji,jj) = rho0 * (  1._wp - EXP( -zhdep(ji,jj) / hcri_iwm(ji,jj) )  ) 
     
    170170      END_2D 
    171171!!gm gde3w ==>>>  check for ssh taken into account.... seem OK gde3w_n=gdept(:,:,:,Kmm) - ssh(:,:,Kmm) 
    172       DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     172      DO_3D( 0, 0, 0, 0, 2, jpkm1 )   ! complete with the level-dependent part 
    173173         IF ( zfact(ji,jj) == 0._wp .OR. wmask(ji,jj,jk) == 0._wp ) THEN   ! optimization 
    174174            zemx_iwm(ji,jj,jk) = 0._wp 
     
    293293      END_3D 
    294294      ! 
    295       IF( ln_mevar ) THEN              ! Variable mixing efficiency case : modify zav_wave in the 
    296          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     295      IF( ln_mevar ) THEN                ! Variable mixing efficiency case : modify zav_wave in the 
     296         DO_3D( 0, 0, 0, 0, 2, jpkm1 )   ! energetic (Reb > 480) and buoyancy-controlled (Reb <10.224 ) regimes 
    297297            IF( zReb(ji,jj,jk) > 480.00_wp ) THEN 
    298298               zav_wave(ji,jj,jk) = 3.6515_wp * znu_w(ji,jj,jk) * SQRT( zReb(ji,jj,jk) ) 
     
    303303      ENDIF 
    304304      ! 
    305       DO_3D( 0, 0, 0, 0, 2, jpkm1 )          ! Bound diffusivity by molecular value and 100 cm2/s 
     305      DO_3D( 0, 0, 0, 0, 2, jpkm1 )      ! Bound diffusivity by molecular value and 100 cm2/s 
    306306         zav_wave(ji,jj,jk) = MIN(  MAX( 1.4e-7_wp, zav_wave(ji,jj,jk) ), 1.e-2_wp  ) * wmask(ji,jj,jk) 
    307307      END_3D 
     
    330330      !                          ! ----------------------- ! 
    331331      !       
    332       IF( ln_tsdiff ) THEN          !* Option for differential mixing of salinity and temperature 
     332      IF( ln_tsdiff ) THEN                !* Option for differential mixing of salinity and temperature 
    333333         ztmp1 = 0.505_wp + 0.495_wp * TANH( 0.92_wp * ( LOG10( 1.e-20_wp ) - 0.60_wp ) ) 
    334          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     334         DO_3D( 0, 0, 0, 0, 2, jpkm1 )       ! Calculate S/T diffusivity ratio as a function of Reb 
    335335            ztmp2 = zReb(ji,jj,jk) * 5._wp * r1_6 
    336336            IF ( ztmp2 > 1.e-20_wp .AND. wmask(ji,jj,jk) == 1._wp ) THEN 
     
    347347         END_3D 
    348348         ! 
    349       ELSE                          !* update momentum & tracer diffusivity with wave-driven mixing 
     349      ELSE                                !* update momentum & tracer diffusivity with wave-driven mixing 
    350350         DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
    351351            p_avs(ji,jj,jk) = p_avs(ji,jj,jk) + zav_wave(ji,jj,jk) 
     
    355355      ENDIF 
    356356 
    357       !                             !* output internal wave-driven mixing coefficient 
     357      !                                   !* output internal wave-driven mixing coefficient 
    358358      CALL iom_put( "av_wave", zav_wave ) 
    359                                     !* output useful diagnostics: Kz*N^2 ,  
     359                                          !* output useful diagnostics: Kz*N^2 ,  
    360360!!gm Kz*N2 should take into account the ratio avs/avt if it is used.... (see diaar5) 
    361                                     !  vertical integral of rho0 * Kz * N^2 , energy density (zemx_iwm) 
     361                                          !  vertical integral of rho0 * Kz * N^2 , energy density (zemx_iwm) 
    362362      IF( iom_use("bflx_iwm") .OR. iom_use("pcmap_iwm") ) THEN 
    363363         ALLOCATE( z2d(jpi,jpj) , z3d(jpi,jpj,jpk) ) 
  • NEMO/trunk/src/OCE/ZDF/zdfmxl.F90

    r13295 r13497  
    9696      ! 
    9797      ! w-level of the mixing and mixed layers 
    98       nmln(:,:)  = nlb10               ! Initialization to the number of w ocean point 
    99       hmlp(:,:)  = 0._wp               ! here hmlp used as a dummy variable, integrating vertically N^2 
    100       zN2_c = grav * rho_c * r1_rho0   ! convert density criteria into N^2 criteria 
    101       DO_3D( 1, 1, 1, 1, nlb10, jpkm1 ) 
     98      nmln(:,:)  = nlb10                  ! Initialization to the number of w ocean point 
     99      hmlp(:,:)  = 0._wp                  ! here hmlp used as a dummy variable, integrating vertically N^2 
     100      zN2_c = grav * rho_c * r1_rho0      ! convert density criteria into N^2 criteria 
     101      DO_3D( 1, 1, 1, 1, nlb10, jpkm1 )   ! Mixed layer level: w-level 
    102102         ikt = mbkt(ji,jj) 
    103103         hmlp(ji,jj) =   & 
     
    107107      ! 
    108108      ! w-level of the turbocline and mixing layer (iom_use) 
    109       imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point 
    110       DO_3DS( 1, 1, 1, 1, jpkm1, nlb10, -1 ) 
     109      imld(:,:) = mbkt(:,:) + 1                ! Initialization to the number of w ocean point 
     110      DO_3DS( 1, 1, 1, 1, jpkm1, nlb10, -1 )   ! from the bottom to nlb10 
    111111         IF( avt (ji,jj,jk) < avt_c * wmask(ji,jj,jk) )   imld(ji,jj) = jk      ! Turbocline  
    112112      END_3D 
  • NEMO/trunk/src/OCE/ZDF/zdfosm.F90

    r13295 r13497  
    11841184! KPP-style Ri# mixing 
    11851185       IF( ln_kpprimix) THEN 
    1186           DO_3D( 1, 0, 1, 0, 2, jpkm1 ) 
     1186          DO_3D( 1, 0, 1, 0, 2, jpkm1 )      !* Shear production at uw- and vw-points (energy conserving form) 
    11871187             z3du(ji,jj,jk) = 0.5 * (  uu(ji,jj,jk-1,Kmm) -  uu(ji  ,jj,jk,Kmm) )   & 
    11881188                  &                 * (  uu(ji,jj,jk-1,Kbb) -  uu(ji  ,jj,jk,Kbb) ) * wumask(ji,jj,jk) & 
     
    15161516     ! 
    15171517     hbl(:,:)  = 0._wp              ! here hbl used as a dummy variable, integrating vertically N^2 
    1518      DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     1518     DO_3D( 1, 1, 1, 1, 1, jpkm1 )  ! Mixed layer level: w-level 
    15191519        ikt = mbkt(ji,jj) 
    15201520        hbl(ji,jj) = hbl(ji,jj) + MAX( rn2(ji,jj,jk) , 0._wp ) * e3w(ji,jj,jk,Kmm) 
     
    16291629      !code saving tracer trends removed, replace with trdmxl_oce 
    16301630 
    1631       DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     1631      DO_3D( 0, 0, 0, 0, 1, jpkm1 )       ! add non-local u and v fluxes 
    16321632         puu(ji,jj,jk,Krhs) =  puu(ji,jj,jk,Krhs)                      & 
    16331633            &                 - (  ghamu(ji,jj,jk  )  & 
  • NEMO/trunk/src/OCE/ZDF/zdfric.F90

    r13295 r13497  
    160160      ! 
    161161      !                       !==  avm and avt = F(Richardson number)  ==! 
    162       DO_3D( 1, 0, 1, 0, 2, jpkm1 ) 
     162      DO_3D( 1, 0, 1, 0, 2, jpkm1 )       ! coefficient = F(richardson number) (avm-weighted Ri) 
    163163         zcfRi = 1._wp / (  1._wp + rn_alp * MAX(  0._wp , avm(ji,jj,jk) * rn2(ji,jj,jk) / ( p_sh2(ji,jj,jk) + 1.e-20 ) )  ) 
    164164         zav   = rn_avmri * zcfRi**nn_ric 
     
    173173      IF( ln_mldw ) THEN      !==  set a minimum value in the Ekman layer  ==! 
    174174         ! 
    175          DO_2D( 0, 0, 0, 0 ) 
     175         DO_2D( 0, 0, 0, 0 )             !* Ekman depth 
    176176            zustar = SQRT( taum(ji,jj) * r1_rho0 ) 
    177177            zhek   = rn_ekmfc * zustar / ( ABS( ff_t(ji,jj) ) + rsmall )   ! Ekman depth 
    178178            zh_ekm(ji,jj) = MAX(  rn_mldmin , MIN( zhek , rn_mldmax )  )   ! set allowed range 
    179179         END_2D 
    180          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     180         DO_3D( 0, 0, 0, 0, 2, jpkm1 )   !* minimum mixing coeff. within the Ekman layer 
    181181            IF( gdept(ji,jj,jk,Kmm) < zh_ekm(ji,jj) ) THEN 
    182182               p_avm(ji,jj,jk) = MAX(  p_avm(ji,jj,jk), rn_wvmix  ) * wmask(ji,jj,jk) 
  • NEMO/trunk/src/OCE/ZDF/zdfsh2.F90

    r13295 r13497  
    6060      ! 
    6161      DO jk = 2, jpkm1 
    62          DO_2D( 1, 0, 1, 0 ) 
     62         DO_2D( 1, 0, 1, 0 )     !* 2 x shear production at uw- and vw-points (energy conserving form) 
    6363            zsh2u(ji,jj) = ( p_avm(ji+1,jj,jk) + p_avm(ji,jj,jk) ) & 
    6464               &         * (   uu(ji,jj,jk-1,Kmm) -   uu(ji,jj,jk,Kmm) ) & 
     
    7272               &         * wvmask(ji,jj,jk) 
    7373         END_2D 
    74          DO_2D( 0, 0, 0, 0 ) 
     74         DO_2D( 0, 0, 0, 0 )     !* shear production at w-point ! coast mask: =2 at the coast ; =1 otherwise (NB: wmask useless as zsh2 are masked) 
    7575            p_sh2(ji,jj,jk) = 0.25 * (   ( zsh2u(ji-1,jj) + zsh2u(ji,jj) ) * ( 2. - umask(ji-1,jj,jk) * umask(ji,jj,jk) )   & 
    7676               &                       + ( zsh2v(ji,jj-1) + zsh2v(ji,jj) ) * ( 2. - vmask(ji,jj-1,jk) * vmask(ji,jj,jk) )   ) 
  • NEMO/trunk/src/OCE/ZDF/zdftke.F90

    r13472 r13497  
    238238      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    239239      ! 
    240       DO_2D( 0, 0, 0, 0 ) 
     240      DO_2D( 0, 0, 0, 0 )         ! en(1)   = rn_ebb taum / rau0  (min value rn_emin0) 
    241241!! clem: this should be the right formulation but it makes the model unstable unless drags are calculated implicitly 
    242242!!       one way around would be to increase zbbirau  
     
    325325      !                     ! zdiag : diagonal zd_up : upper diagonal zd_lw : lower diagonal 
    326326      ! 
    327       IF( nn_pdl == 1 ) THEN      !* Prandtl number = F( Ri ) 
     327      IF( nn_pdl == 1 ) THEN          !* Prandtl number = F( Ri ) 
    328328         DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
    329329            !                             ! local Richardson number 
     
    338338      ENDIF 
    339339      !          
    340       DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     340      DO_3D( 0, 0, 0, 0, 2, jpkm1 )   !* Matrix and right hand side in en 
    341341         zcof   = zfact1 * tmask(ji,jj,jk) 
    342342         !                                   ! A minimum of 2.e-5 m2/s is imposed on TKE vertical 
     
    358358      END_3D 
    359359      !                          !* Matrix inversion from level 2 (tke prescribed at level 1) 
    360       DO_3D( 0, 0, 0, 0, 3, jpkm1 ) 
     360      DO_3D( 0, 0, 0, 0, 3, jpkm1 )                ! First recurrence : Dk = Dk - Lk * Uk-1 / Dk-1 
    361361         zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    362362      END_3D 
    363       DO_2D( 0, 0, 0, 0 ) 
     363      DO_2D( 0, 0, 0, 0 )                          ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    364364         zd_lw(ji,jj,2) = en(ji,jj,2) - zd_lw(ji,jj,2) * en(ji,jj,1)    ! Surface boudary conditions on tke 
    365365      END_2D 
     
    367367         zd_lw(ji,jj,jk) = en(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) *zd_lw(ji,jj,jk-1) 
    368368      END_3D 
    369       DO_2D( 0, 0, 0, 0 ) 
     369      DO_2D( 0, 0, 0, 0 )                          ! thrid recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    370370         en(ji,jj,jpkm1) = zd_lw(ji,jj,jpkm1) / zdiag(ji,jj,jpkm1) 
    371371      END_2D 
     
    373373         en(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * en(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    374374      END_3D 
    375       DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     375      DO_3D( 0, 0, 0, 0, 2, jpkm1 )                ! set the minimum value of tke 
    376376         en(ji,jj,jk) = MAX( en(ji,jj,jk), rn_emin ) * wmask(ji,jj,jk) 
    377377      END_3D 
     
    396396         END_2D 
    397397      ELSEIF( nn_etau == 3 ) THEN       !* penetration belox the mixed layer (HF variability) 
    398          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     398         DO_3D( 0, 0, 0, 0, 2, jpkm1 )         ! nn_eice=0 : ON below sea-ice ; nn_eice>0 : partly OFF 
    399399            ztx2 = utau(ji-1,jj  ) + utau(ji,jj) 
    400400            zty2 = vtau(ji  ,jj-1) + vtau(ji,jj) 
     
    470470         zraug = vkarmn * 2.e5_wp / ( rho0 * grav ) 
    471471#if ! defined key_si3 && ! defined key_cice 
    472          DO_2D( 0, 0, 0, 0 ) 
     472         DO_2D( 0, 0, 0, 0 )                  ! No sea-ice 
    473473            zmxlm(ji,jj,1) =  zraug * taum(ji,jj) * tmask(ji,jj,1) 
    474474         END_2D 
     
    481481            END_2D 
    482482            ! 
    483          CASE( 1 )                           ! scaling with constant sea-ice thickness 
     483         CASE( 1 )                      ! scaling with constant sea-ice thickness 
    484484            DO_2D( 0, 0, 0, 0 ) 
    485485               zmxlm(ji,jj,1) =  ( ( 1._wp - fr_i(ji,jj) ) * zraug * taum(ji,jj) + & 
     
    487487            END_2D 
    488488            ! 
    489          CASE( 2 )                                 ! scaling with mean sea-ice thickness 
     489         CASE( 2 )                      ! scaling with mean sea-ice thickness 
    490490            DO_2D( 0, 0, 0, 0 ) 
    491491#if defined key_si3 
     
    499499            END_2D 
    500500            ! 
    501          CASE( 3 )                                 ! scaling with max sea-ice thickness 
     501         CASE( 3 )                      ! scaling with max sea-ice thickness 
    502502            DO_2D( 0, 0, 0, 0 ) 
    503503               zmaxice = MAXVAL( h_i(ji,jj,:) ) 
     
    551551         ! 
    552552      CASE ( 2 )           ! |dk[xml]| bounded by e3t : 
    553          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     553         DO_3D( 0, 0, 0, 0, 2, jpkm1 )        ! from the surface to the bottom : 
    554554            zmxlm(ji,jj,jk) =   & 
    555555               &    MIN( zmxlm(ji,jj,jk-1) + e3t(ji,jj,jk-1,Kmm), zmxlm(ji,jj,jk) ) 
    556556         END_3D 
    557          DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 ) 
     557         DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 )   ! from the bottom to the surface : 
    558558            zemxl = MIN( zmxlm(ji,jj,jk+1) + e3t(ji,jj,jk+1,Kmm), zmxlm(ji,jj,jk) ) 
    559559            zmxlm(ji,jj,jk) = zemxl 
     
    562562         ! 
    563563      CASE ( 3 )           ! lup and ldown, |dk[xml]| bounded by e3t : 
    564          DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
     564         DO_3D( 0, 0, 0, 0, 2, jpkm1 )        ! from the surface to the bottom : lup 
    565565            zmxld(ji,jj,jk) =    & 
    566566               &    MIN( zmxld(ji,jj,jk-1) + e3t(ji,jj,jk-1,Kmm), zmxlm(ji,jj,jk) ) 
    567567         END_3D 
    568          DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 ) 
     568         DO_3DS( 0, 0, 0, 0, jpkm1, 2, -1 )   ! from the bottom to the surface : ldown 
    569569            zmxlm(ji,jj,jk) =   & 
    570570               &    MIN( zmxlm(ji,jj,jk+1) + e3t(ji,jj,jk+1,Kmm), zmxlm(ji,jj,jk) ) 
     
    582582      !                     !  Vertical eddy viscosity and diffusivity  (avm and avt) 
    583583      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    584       DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     584      DO_3D( 0, 0, 0, 0, 1, jpkm1 )   !* vertical eddy viscosity & diffivity at w-points 
    585585         zsqen = SQRT( en(ji,jj,jk) ) 
    586586         zav   = rn_ediff * zmxlm(ji,jj,jk) * zsqen 
     
    591591      ! 
    592592      ! 
    593       IF( nn_pdl == 1 ) THEN      !* Prandtl number case: update avt 
     593      IF( nn_pdl == 1 ) THEN          !* Prandtl number case: update avt 
    594594         DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
    595595            p_avt(ji,jj,jk)   = MAX( apdlr(ji,jj,jk) * p_avt(ji,jj,jk), avtb_2d(ji,jj) * avtb(jk) ) * wmask(ji,jj,jk) 
Note: See TracChangeset for help on using the changeset viewer.