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 13899 for NEMO/branches/2020/tickets_icb_1900/src/ICE/iceitd.F90 – NEMO

Ignore:
Timestamp:
2020-11-27T17:26:33+01:00 (4 years ago)
Author:
mathiot
Message:

ticket #1900: update branch to trunk and add ICB test case

Location:
NEMO/branches/2020/tickets_icb_1900
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/tickets_icb_1900

    • Property svn:externals
      •  

        old new  
        22^/utils/build/makenemo@HEAD   makenemo 
        33^/utils/build/mk@HEAD         mk 
        4 ^/utils/tools/@HEAD           tools 
         4^/utils/tools@HEAD            tools 
        55^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
         
        88 
        99# SETTE 
        10 ^/utils/CI/sette@12931        sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/tickets_icb_1900/src/ICE/iceitd.F90

    r13226 r13899  
    4747   LOGICAL                    ::   ln_cat_usr   ! ice categories are defined by rn_catbnd 
    4848   REAL(wp), DIMENSION(0:100) ::   rn_catbnd    ! ice categories bounds 
     49   REAL(wp)                   ::   rn_himax     ! maximum ice thickness allowed 
    4950   ! 
    5051   !! * Substitutions 
     
    9899      ! 
    99100      npti = 0   ;   nptidx(:) = 0 
    100       DO_2D_11_11 
     101      DO_2D( 1, 1, 1, 1 ) 
    101102         IF ( at_i(ji,jj) > epsi10 ) THEN 
    102103            npti = npti + 1 
     
    314315            IF ( a_i_1d(ji) > epsi10 .AND. h_i_1d(ji) < rn_himin ) THEN 
    315316               a_i_1d(ji) = a_i_1d(ji) * h_i_1d(ji) / rn_himin  
    316                IF( ln_pnd_H12 )   a_ip_1d(ji) = a_ip_1d(ji) * h_i_1d(ji) / rn_himin 
     317               IF( ln_pnd_LEV )   a_ip_1d(ji) = a_ip_1d(ji) * h_i_1d(ji) / rn_himin 
    317318               h_i_1d(ji) = rn_himin 
    318319            ENDIF 
     
    420421      CALL tab_3d_2d( npti, nptidx(1:npti), a_ip_2d(1:npti,1:jpl), a_ip ) 
    421422      CALL tab_3d_2d( npti, nptidx(1:npti), v_ip_2d(1:npti,1:jpl), v_ip ) 
     423      CALL tab_3d_2d( npti, nptidx(1:npti), v_il_2d(1:npti,1:jpl), v_il ) 
    422424      CALL tab_3d_2d( npti, nptidx(1:npti), t_su_2d(1:npti,1:jpl), t_su ) 
    423425      DO jl = 1, jpl 
     
    484486               zaTsfn(ji,jl2)  = zaTsfn(ji,jl2) + ztrans 
    485487               !   
    486                IF ( ln_pnd_H12 ) THEN 
     488               IF ( ln_pnd_LEV ) THEN 
    487489                  ztrans          = a_ip_2d(ji,jl1) * zworka(ji)     ! Pond fraction 
    488490                  a_ip_2d(ji,jl1) = a_ip_2d(ji,jl1) - ztrans 
     
    492494                  v_ip_2d(ji,jl1) = v_ip_2d(ji,jl1) - ztrans 
    493495                  v_ip_2d(ji,jl2) = v_ip_2d(ji,jl2) + ztrans 
     496                  ! 
     497                  IF ( ln_pnd_lids ) THEN                            ! Pond lid volume 
     498                     ztrans          = v_il_2d(ji,jl1) * zworka(ji) 
     499                     v_il_2d(ji,jl1) = v_il_2d(ji,jl1) - ztrans 
     500                     v_il_2d(ji,jl2) = v_il_2d(ji,jl2) + ztrans 
     501                  ENDIF 
    494502               ENDIF 
    495503               ! 
     
    536544      ! clem: The transfer between one category to another can lead to very small negative values (-1.e-20) 
    537545      !       because of truncation error ( i.e. 1. - 1. /= 0 ) 
    538       CALL ice_var_roundoff( a_i_2d, v_i_2d, v_s_2d, sv_i_2d, oa_i_2d, a_ip_2d, v_ip_2d, ze_s_2d, ze_i_2d ) 
     546      CALL ice_var_roundoff( a_i_2d, v_i_2d, v_s_2d, sv_i_2d, oa_i_2d, a_ip_2d, v_ip_2d, v_il_2d, ze_s_2d, ze_i_2d ) 
    539547 
    540548      ! at_i must be <= rn_amax 
     
    568576      CALL tab_2d_3d( npti, nptidx(1:npti), a_ip_2d(1:npti,1:jpl), a_ip ) 
    569577      CALL tab_2d_3d( npti, nptidx(1:npti), v_ip_2d(1:npti,1:jpl), v_ip ) 
     578      CALL tab_2d_3d( npti, nptidx(1:npti), v_il_2d(1:npti,1:jpl), v_il ) 
    570579      CALL tab_2d_3d( npti, nptidx(1:npti), t_su_2d(1:npti,1:jpl), t_su ) 
    571580      DO jl = 1, jpl 
     
    611620         !                    !--------------------------------------- 
    612621         npti = 0   ;   nptidx(:) = 0 
    613          DO_2D_11_11 
     622         DO_2D( 1, 1, 1, 1 ) 
    614623            IF( a_i(ji,jj,jl) > 0._wp .AND. v_i(ji,jj,jl) > (a_i(ji,jj,jl) * hi_max(jl)) ) THEN 
    615624               npti = npti + 1 
     
    618627         END_2D 
    619628         ! 
    620 !!clem   CALL tab_2d_1d( npti, nptidx(1:npti), h_i_1d(1:npti), h_i(:,:,jl) ) 
    621          CALL tab_2d_1d( npti, nptidx(1:npti), a_i_1d(1:npti), a_i(:,:,jl) ) 
    622          CALL tab_2d_1d( npti, nptidx(1:npti), v_i_1d(1:npti), v_i(:,:,jl) ) 
    623          ! 
    624          DO ji = 1, npti 
    625             jdonor(ji,jl)  = jl  
    626             ! how much of a_i you send in cat sup is somewhat arbitrary 
    627 !!clem: these do not work properly after a restart (I do not know why) => not sure it is still true 
    628 !!          zdaice(ji,jl)  = a_i_1d(ji) * ( h_i_1d(ji) - hi_max(jl) + epsi10 ) / h_i_1d(ji)   
    629 !!          zdvice(ji,jl)  = v_i_1d(ji) - ( a_i_1d(ji) - zdaice(ji,jl) ) * ( hi_max(jl) - epsi10 ) 
    630 !!clem: these do not work properly after a restart (I do not know why) => not sure it is still true 
    631 !!          zdaice(ji,jl)  = a_i_1d(ji) 
    632 !!          zdvice(ji,jl)  = v_i_1d(ji) 
    633 !!clem: these are from UCL and work ok 
    634             zdaice(ji,jl)  = a_i_1d(ji) * 0.5_wp 
    635             zdvice(ji,jl)  = v_i_1d(ji) - zdaice(ji,jl) * ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp 
    636          END DO 
    637          ! 
    638          IF( npti > 0 ) THEN 
     629         IF( npti > 0 ) THEN             
     630            !!clem   CALL tab_2d_1d( npti, nptidx(1:npti), h_i_1d(1:npti), h_i(:,:,jl) ) 
     631            CALL tab_2d_1d( npti, nptidx(1:npti), a_i_1d(1:npti), a_i(:,:,jl) ) 
     632            CALL tab_2d_1d( npti, nptidx(1:npti), v_i_1d(1:npti), v_i(:,:,jl) ) 
     633            ! 
     634            DO ji = 1, npti 
     635               jdonor(ji,jl)  = jl  
     636               ! how much of a_i you send in cat sup is somewhat arbitrary 
     637               !!clem: these do not work properly after a restart (I do not know why) => not sure it is still true 
     638               !!          zdaice(ji,jl)  = a_i_1d(ji) * ( h_i_1d(ji) - hi_max(jl) + epsi10 ) / h_i_1d(ji)   
     639               !!          zdvice(ji,jl)  = v_i_1d(ji) - ( a_i_1d(ji) - zdaice(ji,jl) ) * ( hi_max(jl) - epsi10 ) 
     640               !!clem: these do not work properly after a restart (I do not know why) => not sure it is still true 
     641               !!          zdaice(ji,jl)  = a_i_1d(ji) 
     642               !!          zdvice(ji,jl)  = v_i_1d(ji) 
     643               !!clem: these are from UCL and work ok 
     644               zdaice(ji,jl)  = a_i_1d(ji) * 0.5_wp 
     645               zdvice(ji,jl)  = v_i_1d(ji) - zdaice(ji,jl) * ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp 
     646            END DO 
     647            ! 
    639648            CALL itd_shiftice( jdonor(1:npti,:), zdaice(1:npti,:), zdvice(1:npti,:) )  ! Shift jl=>jl+1 
    640649            ! Reset shift parameters 
     
    650659         !                    !----------------------------------------- 
    651660         npti = 0 ; nptidx(:) = 0 
    652          DO_2D_11_11 
     661         DO_2D( 1, 1, 1, 1 ) 
    653662            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 
    654663               npti = npti + 1 
     
    657666         END_2D 
    658667         ! 
    659          CALL tab_2d_1d( npti, nptidx(1:npti), a_i_1d(1:npti), a_i(:,:,jl+1) ) ! jl+1 is ok 
    660          CALL tab_2d_1d( npti, nptidx(1:npti), v_i_1d(1:npti), v_i(:,:,jl+1) ) ! jl+1 is ok 
    661          DO ji = 1, npti 
    662             jdonor(ji,jl) = jl + 1 
    663             zdaice(ji,jl) = a_i_1d(ji)  
    664             zdvice(ji,jl) = v_i_1d(ji) 
    665          END DO 
    666          ! 
    667668         IF( npti > 0 ) THEN 
     669            CALL tab_2d_1d( npti, nptidx(1:npti), a_i_1d(1:npti), a_i(:,:,jl+1) ) ! jl+1 is ok 
     670            CALL tab_2d_1d( npti, nptidx(1:npti), v_i_1d(1:npti), v_i(:,:,jl+1) ) ! jl+1 is ok 
     671            DO ji = 1, npti 
     672               jdonor(ji,jl) = jl + 1 
     673               zdaice(ji,jl) = a_i_1d(ji)  
     674               zdvice(ji,jl) = v_i_1d(ji) 
     675            END DO 
     676            ! 
    668677            CALL itd_shiftice( jdonor(1:npti,:), zdaice(1:npti,:), zdvice(1:npti,:) )  ! Shift jl+1=>jl 
    669678            ! Reset shift parameters 
     
    693702      REAL(wp) ::   zhmax, znum, zden, zalpha   !   -      - 
    694703      ! 
    695       NAMELIST/namitd/ ln_cat_hfn, rn_himean, ln_cat_usr, rn_catbnd, rn_himin 
     704      NAMELIST/namitd/ ln_cat_hfn, rn_himean, ln_cat_usr, rn_catbnd, rn_himin, rn_himax 
    696705      !!------------------------------------------------------------------ 
    697706      ! 
     
    710719         WRITE(numout,*) '         mean ice thickness in the domain                               rn_himean  = ', rn_himean 
    711720         WRITE(numout,*) '      Ice categories are defined by rn_catbnd                           ln_cat_usr = ', ln_cat_usr 
    712          WRITE(numout,*) '      minimum ice thickness                                             rn_himin   = ', rn_himin  
     721         WRITE(numout,*) '      minimum ice thickness allowed                                     rn_himin   = ', rn_himin  
     722         WRITE(numout,*) '      maximum ice thickness allowed                                     rn_himax   = ', rn_himax  
    713723      ENDIF 
    714724      ! 
     
    747757      END DO 
    748758      ! 
    749       hi_max(jpl) = 99._wp          ! set to a big value to ensure that all ice is thinner than hi_max(jpl) 
     759      hi_max(jpl) = rn_himax        ! set to a big value to ensure that all ice is thinner than hi_max(jpl) 
    750760      ! 
    751761      IF(lwp) WRITE(numout,*) 
Note: See TracChangeset for help on using the changeset viewer.