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 14997 – NEMO

Changeset 14997


Ignore:
Timestamp:
2021-06-16T08:43:57+02:00 (3 years ago)
Author:
smasson
Message:

trunk, ICE: replace DO_?D( 1, 1, 1, 1 ) by DO_?D( nn_hls, nn_hls, nn_hls, nn_hls ) except for icedyn_adv_* and icedyn_rhg_*, #2668

Location:
NEMO/trunk/src/ICE
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/icealb.F90

    r13472 r14997  
    124124      ! 
    125125      DO jl = 1, jpl 
    126          DO_2D( 1, 1, 1, 1 ) 
     126         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )   ! palb_ice used over the full domain in icesbc 
    127127            ! 
    128128            !---------------------------------------------! 
  • NEMO/trunk/src/ICE/icecor.F90

    r14433 r14997  
    9191         zzc = rhoi * r1_Dt_ice 
    9292         DO jl = 1, jpl 
    93             DO_2D( 1, 1, 1, 1 ) 
     93            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    9494               zsal = sv_i(ji,jj,jl) 
    9595               sv_i(ji,jj,jl) = MIN(  MAX( rn_simin*v_i(ji,jj,jl) , sv_i(ji,jj,jl) ) , rn_simax*v_i(ji,jj,jl)  ) 
  • NEMO/trunk/src/ICE/icectl.F90

    r14595 r14997  
    391391      cl_alname(ialert_id) = ' Very high salinity ' ! name of the alert 
    392392      DO jl = 1, jpl 
    393          DO_2D( 1, 1, 1, 1 ) 
     393         DO_2D( 0, 0, 0, 0 ) 
    394394            IF( v_i(ji,jj,jl) > epsi10  ) THEN 
    395395               IF( sv_i(ji,jj,jl) / v_i(ji,jj,jl) > rn_simax ) THEN 
     
    406406      cl_alname(ialert_id) = ' Very low salinity ' ! name of the alert 
    407407      DO jl = 1, jpl 
    408          DO_2D( 1, 1, 1, 1 ) 
     408         DO_2D( 0, 0, 0, 0 ) 
    409409            IF( v_i(ji,jj,jl) > epsi10  ) THEN 
    410410               IF( sv_i(ji,jj,jl) / v_i(ji,jj,jl) < rn_simin ) THEN 
     
    421421      cl_alname(ialert_id) = ' Very cold ice ' ! name of the alert 
    422422      DO jl = 1, jpl 
    423          DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     423         DO_3D( 0, 0, 0, 0, 1, nlay_i ) 
    424424            ztmelts    =  -rTmlt * sz_i(ji,jj,jk,jl) + rt0 
    425425            IF( t_i(ji,jj,jk,jl) < -50.+rt0  .AND.  v_i(ji,jj,jl) > epsi10 ) THEN 
     
    435435      cl_alname(ialert_id) = ' Very warm ice ' ! name of the alert 
    436436      DO jl = 1, jpl 
    437          DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     437         DO_3D( 0, 0, 0, 0, 1, nlay_i ) 
    438438            ztmelts    =  -rTmlt * sz_i(ji,jj,jk,jl) + rt0 
    439439            IF( t_i(ji,jj,jk,jl) > ztmelts  .AND.  v_i(ji,jj,jl) > epsi10 ) THEN 
     
    449449      cl_alname(ialert_id) = ' Very thick ice ' ! name of the alert 
    450450      jl = jpl 
    451       DO_2D( 1, 1, 1, 1 ) 
     451      DO_2D( 0, 0, 0, 0 ) 
    452452         IF( h_i(ji,jj,jl) > 50._wp ) THEN 
    453453            WRITE(numout,*) ' ALERTE :   Very thick ice ',h_i(ji,jj,jl) 
     
    461461      cl_alname(ialert_id) = ' Very thin ice ' ! name of the alert 
    462462      jl = 1 
    463       DO_2D( 1, 1, 1, 1 ) 
     463      DO_2D( 0, 0, 0, 0 ) 
    464464         IF( h_i(ji,jj,jl) < rn_himin ) THEN 
    465465            WRITE(numout,*) ' ALERTE :   Very thin ice ',h_i(ji,jj,jl) 
     
    472472      ialert_id = ialert_id + 1 ! reference number of this alert 
    473473      cl_alname(ialert_id) = ' Very fast ice ' ! name of the alert 
    474       DO_2D( 1, 1, 1, 1 ) 
     474      DO_2D( 0, 0, 0, 0 ) 
    475475         IF( MAX( ABS( u_ice(ji,jj) ), ABS( v_ice(ji,jj) ) ) > 2. ) THEN 
    476476            WRITE(numout,*) ' ALERTE :   Very fast ice ',MAX( ABS( u_ice(ji,jj) ), ABS( v_ice(ji,jj) ) ) 
     
    483483      ialert_id = ialert_id + 1 ! reference number of this alert 
    484484      cl_alname(ialert_id) = ' Ice on continents ' ! name of the alert 
    485       DO_2D( 1, 1, 1, 1 ) 
     485      DO_2D( 0, 0, 0, 0 ) 
    486486         IF( tmask(ji,jj,1) == 0._wp .AND. ( at_i(ji,jj) > 0._wp .OR. vt_i(ji,jj) > 0._wp ) ) THEN 
    487487            WRITE(numout,*) ' ALERTE :   Ice on continents ',at_i(ji,jj),vt_i(ji,jj) 
     
    494494      ialert_id = ialert_id + 1 ! reference number of this alert 
    495495      cl_alname(ialert_id) = ' Incompatible ice conc and vol ' ! name of the alert 
    496       DO_2D( 1, 1, 1, 1 ) 
     496      DO_2D( 0, 0, 0, 0 ) 
    497497         IF(  ( vt_i(ji,jj) == 0._wp .AND. at_i(ji,jj) >  0._wp ) .OR. & 
    498498            & ( vt_i(ji,jj) >  0._wp .AND. at_i(ji,jj) == 0._wp ) ) THEN 
     
    775775      ! 2D budgets (must be close to 0) 
    776776      IF( iom_use('icedrift_mass') .OR. iom_use('icedrift_salt') .OR. iom_use('icedrift_heat') ) THEN 
    777          DO_2D( 1, 1, 1, 1 ) 
     777         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    778778            zdiag_mass2D(ji,jj) = wfx_ice(ji,jj)   + wfx_snw(ji,jj)   + wfx_spr(ji,jj)   + wfx_sub(ji,jj) + wfx_pnd(ji,jj) & 
    779779               &                + diag_vice(ji,jj) + diag_vsnw(ji,jj) + diag_vpnd(ji,jj) - diag_adv_mass(ji,jj) 
  • NEMO/trunk/src/ICE/icedyn.F90

    r14072 r14997  
    135135         ! CFL = 0.5 at a distance from the bound of 1/6 of the basin length 
    136136         ! Then for dx = 2m and dt = 1s => rn_uice = u (1/6th) = 1m/s 
    137          DO_2D( 1, 1, 1, 1 ) 
     137         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    138138            zcoefu = ( REAL(jpiglo+1)*0.5_wp - REAL(ji+nimpp-1) ) / ( REAL(jpiglo+1)*0.5_wp - 1._wp ) 
    139139            zcoefv = ( REAL(jpjglo+1)*0.5_wp - REAL(jj+njmpp-1) ) / ( REAL(jpjglo+1)*0.5_wp - 1._wp ) 
  • NEMO/trunk/src/ICE/icedyn_rdgrft.F90

    r14072 r14997  
    162162      npti = 0   ;   nptidx(:) = 0 
    163163      ipti = 0   ;   iptidx(:) = 0 
    164       DO_2D( 1, 1, 1, 1 ) 
     164      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    165165         IF ( at_i(ji,jj) > epsi10 ) THEN 
    166166            npti           = npti + 1 
  • NEMO/trunk/src/ICE/iceistate.F90

    r14143 r14997  
    308308            ! select ice covered grid points 
    309309            npti = 0 ; nptidx(:) = 0 
    310             DO_2D( 1, 1, 1, 1 ) 
     310            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    311311               IF ( zht_i_ini(ji,jj) > 0._wp ) THEN 
    312312                  npti         = npti  + 1 
     
    363363            CALL ice_var_salprof ! for sz_i 
    364364            DO jl = 1, jpl 
    365                DO_2D( 1, 1, 1, 1 ) 
     365               DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    366366                  v_i (ji,jj,jl) = h_i(ji,jj,jl) * a_i(ji,jj,jl) 
    367367                  v_s (ji,jj,jl) = h_s(ji,jj,jl) * a_i(ji,jj,jl) 
     
    371371            ! 
    372372            DO jl = 1, jpl 
    373                DO_3D( 1, 1, 1, 1, 1, nlay_s ) 
     373               DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_s ) 
    374374                  t_s(ji,jj,jk,jl) = zts_3d(ji,jj,jl) 
    375375                  e_s(ji,jj,jk,jl) = zswitch(ji,jj) * v_s(ji,jj,jl) * r1_nlay_s * & 
     
    379379            ! 
    380380            DO jl = 1, jpl 
    381                DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     381               DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    382382                  t_i (ji,jj,jk,jl) = zti_3d(ji,jj,jl)  
    383383                  ztmelts          = - rTmlt * sz_i(ji,jj,jk,jl) + rt0 ! melting temperature in K 
  • NEMO/trunk/src/ICE/iceitd.F90

    r14072 r14997  
    101101      ! 
    102102      npti = 0   ;   nptidx(:) = 0 
    103       DO_2D( 1, 1, 1, 1 ) 
     103      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    104104         IF ( at_i(ji,jj) > epsi10 ) THEN 
    105105            npti = npti + 1 
     
    624624         !                    !--------------------------------------- 
    625625         npti = 0   ;   nptidx(:) = 0 
    626          DO_2D( 1, 1, 1, 1 ) 
     626         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    627627            IF( a_i(ji,jj,jl) > 0._wp .AND. v_i(ji,jj,jl) > (a_i(ji,jj,jl) * hi_max(jl)) ) THEN 
    628628               npti = npti + 1 
     
    660660         !                    !----------------------------------------- 
    661661         npti = 0 ; nptidx(:) = 0 
    662          DO_2D( 1, 1, 1, 1 ) 
     662         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    663663            IF( a_i(ji,jj,jl+1) > 0._wp .AND. v_i(ji,jj,jl+1) <= (a_i(ji,jj,jl+1) * hi_max(jl)) ) THEN 
    664664               npti = npti + 1 
  • NEMO/trunk/src/ICE/icestp.F90

    r14886 r14997  
    404404      !!---------------------------------------------------------------------- 
    405405 
    406       DO_2D( 1, 1, 1, 1 ) 
     406      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )   ! needed for (at least) diag_adv_mass -> to be removed  
    407407         sfx    (ji,jj) = 0._wp   ; 
    408408         sfx_bri(ji,jj) = 0._wp   ;   sfx_lam(ji,jj) = 0._wp 
     
    452452 
    453453      DO jl = 1, jpl 
    454          DO_2D( 1, 1, 1, 1 ) 
     454         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    455455            ! SIMIP diagnostics 
    456456            t_si       (ji,jj,jl) = rt0     ! temp at the ice-snow interface 
  • NEMO/trunk/src/ICE/icethd.F90

    r14886 r14997  
    141141      ! Partial computation of forcing for the thermodynamic sea ice model 
    142142      !--------------------------------------------------------------------! 
    143       DO_2D( 1, 1, 1, 1 ) 
     143      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )   ! needed for qlead 
    144144         rswitch  = tmask(ji,jj,1) * MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi10 ) ) ! 0 if no ice 
    145145         ! 
     
    226226         ! select ice covered grid points 
    227227         npti = 0 ; nptidx(:) = 0 
    228          DO_2D( 1, 1, 1, 1 ) 
     228         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    229229            IF ( a_i(ji,jj,jl) > epsi10 ) THEN 
    230230               npti         = npti  + 1 
  • NEMO/trunk/src/ICE/icethd_do.F90

    r14433 r14997  
    204204      ! Identify grid points where new ice forms 
    205205      npti = 0   ;   nptidx(:) = 0 
    206       DO_2D( 1, 1, 1, 1 ) 
     206      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    207207         IF ( qlead(ji,jj)  <  0._wp ) THEN 
    208208            npti = npti + 1 
  • NEMO/trunk/src/ICE/icethd_pnd.F90

    r14252 r14997  
    9999      ! 
    100100      DO jl = 1, jpl 
    101          DO_2D( 1, 1, 1, 1 ) 
     101         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    102102            IF( v_i(ji,jj,jl) < epsi10 .OR. at_i(ji,jj) < epsi10 ) THEN 
    103103               wfx_pnd  (ji,jj)    = wfx_pnd(ji,jj) + ( v_ip(ji,jj,jl) + v_il(ji,jj,jl) ) * rhow * r1_Dt_ice 
     
    116116      !------------------------------ 
    117117      npti = 0   ;   nptidx(:) = 0 
    118       DO_2D( 1, 1, 1, 1 ) 
     118      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    119119         IF( at_i(ji,jj) >= epsi10 ) THEN 
    120120            npti = npti + 1 
     
    590590 
    591591      DO jl = 1, jpl 
    592          DO_2D( 1, 1, 1, 1 ) 
     592         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    593593 
    594594               IF ( a_i(ji,jj,jl) > epsi10 ) THEN 
     
    638638      IF( ln_pnd_lids ) THEN 
    639639 
    640          DO_2D( 1, 1, 1, 1 ) 
     640         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    641641 
    642642            IF ( at_i(ji,jj) > 0.01 .AND. hm_i(ji,jj) > rn_himin .AND. zvolp_ini(ji,jj) > zvp_min * at_i(ji,jj) ) THEN 
     
    765765      DO jl = 1, jpl 
    766766 
    767          DO_2D( 1, 1, 1, 1 ) 
     767         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    768768 
    769769!              ! zap lids on small ponds 
     
    869869       h_ip(:,:,:) = 0._wp 
    870870 
    871        DO_2D( 1, 1, 1, 1 ) 
     871       DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    872872 
    873873             IF ( at_i(ji,jj) > 0.01 .AND. hm_i(ji,jj) > rn_himin .AND. zvolp(ji,jj) > zvp_min * at_i(ji,jj) ) THEN 
  • NEMO/trunk/src/ICE/iceupdate.F90

    r14718 r14997  
    120120      ENDIF 
    121121 
    122       DO_2D( 1, 1, 1, 1 ) 
     122      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    123123 
    124124         ! Solar heat flux reaching the ocean (max) = zqsr (W.m-2) 
  • NEMO/trunk/src/ICE/icevar.F90

    r14072 r14997  
    271271      zlay_i   = REAL( nlay_i , wp )    ! number of layers 
    272272      DO jl = 1, jpl 
    273          DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     273         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    274274            IF ( v_i(ji,jj,jl) > epsi20 ) THEN     !--- icy area 
    275275               ! 
     
    376376         z1_dS = 1._wp / ( zsi1 - zsi0 ) 
    377377         DO jl = 1, jpl 
    378             DO_2D( 1, 1, 1, 1 ) 
     378            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    379379               zalpha(ji,jj,jl) = MAX(  0._wp , MIN( ( zsi1 - s_i(ji,jj,jl) ) * z1_dS , 1._wp )  ) 
    380380               !                             ! force a constant profile when SSS too low (Baltic Sea) 
     
    385385         ! Computation of the profile 
    386386         DO jl = 1, jpl 
    387             DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     387            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    388388               !                          ! linear profile with 0 surface value 
    389389               zs0 = z_slope_s(ji,jj,jl) * ( REAL(jk,wp) - 0.5_wp ) * h_i(ji,jj,jl) * r1_nlay_i 
     
    515515         ! Zap ice energy and use ocean heat to melt ice 
    516516         !----------------------------------------------------------------- 
    517          DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     517         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    518518            ! update exchanges with ocean 
    519519            hfx_res(ji,jj)   = hfx_res(ji,jj) - (1._wp - zswitch(ji,jj) ) * e_i(ji,jj,jk,jl) * r1_Dt_ice ! W.m-2 <0 
     
    522522         END_3D 
    523523         ! 
    524          DO_3D( 1, 1, 1, 1, 1, nlay_s ) 
     524         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_s ) 
    525525            ! update exchanges with ocean 
    526526            hfx_res(ji,jj)   = hfx_res(ji,jj) - (1._wp - zswitch(ji,jj) ) * e_s(ji,jj,jk,jl) * r1_Dt_ice ! W.m-2 <0 
     
    532532         ! zap ice and snow volume, add water and salt to ocean 
    533533         !----------------------------------------------------------------- 
    534          DO_2D( 1, 1, 1, 1 ) 
     534         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    535535            ! update exchanges with ocean 
    536536            sfx_res(ji,jj)  = sfx_res(ji,jj) + ( 1._wp - zswitch(ji,jj) ) * sv_i(ji,jj,jl)   * rhoi * r1_Dt_ice 
     
    608608         ! zap ice energy and send it to the ocean 
    609609         !---------------------------------------- 
    610          DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
     610         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    611611            IF( pe_i(ji,jj,jk,jl) < 0._wp .OR. pa_i(ji,jj,jl) <= 0._wp ) THEN 
    612612               hfx_res(ji,jj)   = hfx_res(ji,jj) - pe_i(ji,jj,jk,jl) * z1_dt ! W.m-2 >0 
     
    615615         END_3D 
    616616         ! 
    617          DO_3D( 1, 1, 1, 1, 1, nlay_s ) 
     617         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_s ) 
    618618            IF( pe_s(ji,jj,jk,jl) < 0._wp .OR. pa_i(ji,jj,jl) <= 0._wp ) THEN 
    619619               hfx_res(ji,jj)   = hfx_res(ji,jj) - pe_s(ji,jj,jk,jl) * z1_dt ! W.m-2 <0 
     
    625625         ! zap ice and snow volume, add water and salt to ocean 
    626626         !----------------------------------------------------- 
    627          DO_2D( 1, 1, 1, 1 ) 
     627         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    628628            IF( pv_i(ji,jj,jl) < 0._wp .OR. pa_i(ji,jj,jl) <= 0._wp ) THEN 
    629629               wfx_res(ji,jj)    = wfx_res(ji,jj) + pv_i (ji,jj,jl) * rhoi * z1_dt 
  • NEMO/trunk/src/ICE/icewri.F90

    r14072 r14997  
    7171 
    7272      ! tresholds for outputs 
    73       DO_2D( 1, 1, 1, 1 ) 
     73      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    7474         zmsk00(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06  ) ) ! 1 if ice    , 0 if no ice 
    7575         zmsk05(ji,jj) = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.05_wp ) ) ! 1 if 5% ice , 0 if less 
     
    7878      END_2D 
    7979      DO jl = 1, jpl 
    80          DO_2D( 1, 1, 1, 1 ) 
     80         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    8181            zmsk00l(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
    8282            zmsksnl(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , v_s(ji,jj,jl) - epsi06 ) ) 
Note: See TracChangeset for help on using the changeset viewer.