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 10001 for NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/ICE/iceistate.F90 – NEMO

Ignore:
Timestamp:
2018-07-26T09:50:51+02:00 (6 years ago)
Author:
gm
Message:

#1911 (ENHANCE-04): RK3 branch - step I.1 and I.2 (see wiki page)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/ICE/iceistate.F90

    r9939 r10001  
    9494      REAL(wp) ::   zarg, zV, zconv, zdv, zfac 
    9595      INTEGER , DIMENSION(4)           ::   itest 
    96       REAL(wp), DIMENSION(jpi,jpj)     ::   z2d 
    9796      REAL(wp), DIMENSION(jpi,jpj)     ::   zswitch    ! ice indicator 
    9897      REAL(wp), DIMENSION(jpi,jpj)     ::   zht_i_ini, zat_i_ini, zvt_i_ini            !data from namelist or nc file 
    9998      REAL(wp), DIMENSION(jpi,jpj)     ::   zts_u_ini, zht_s_ini, zsm_i_ini, ztm_i_ini !data from namelist or nc file 
    10099      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zh_i_ini , za_i_ini                        !data by cattegories to fill 
     100      REAL(wp), DIMENSION(jpi,jpj)     ::   z_ssh_h0, zsshu, zsshv, zsshf 
    101101      !-------------------------------------------------------------------- 
    102102 
     
    413413      snwice_mass_b(:,:) = snwice_mass(:,:) 
    414414      ! 
    415       IF( ln_ice_embd ) THEN            ! embedded sea-ice: deplete the initial ssh below sea-ice area 
     415      IF( ln_ice_embd ) THEN           ! embedded sea-ice: deplete the initial ssh below sea-ice area 
    416416         ! 
    417417         sshn(:,:) = sshn(:,:) - snwice_mass(:,:) * r1_rho0 
    418418         sshb(:,:) = sshb(:,:) - snwice_mass(:,:) * r1_rho0 
    419419         ! 
    420          IF( .NOT.ln_linssh ) THEN 
    421             ! 
    422             WHERE( ht_0(:,:) > 0 )   ;   z2d(:,:) = 1._wp + sshn(:,:)*tmask(:,:,1) / ht_0(:,:) 
    423             ELSEWHERE                ;   z2d(:,:) = 1._wp   ;   END WHERE 
    424             ! 
    425             DO jk = 1,jpkm1                     ! adjust initial vertical scale factors                 
    426                e3t_n(:,:,jk) = e3t_0(:,:,jk) * z2d(:,:) 
    427                e3t_b(:,:,jk) = e3t_n(:,:,jk) 
    428                e3t_a(:,:,jk) = e3t_n(:,:,jk) 
    429             END DO 
    430             ! 
    431             ! Reconstruction of all vertical scale factors at now and before time-steps 
    432             ! ========================================================================= 
    433             ! Horizontal scale factor interpolations 
    434             ! -------------------------------------- 
    435             CALL dom_vvl_interpol( e3t_b(:,:,:), e3u_b(:,:,:), 'U' ) 
    436             CALL dom_vvl_interpol( e3t_b(:,:,:), e3v_b(:,:,:), 'V' ) 
    437             CALL dom_vvl_interpol( e3t_n(:,:,:), e3u_n(:,:,:), 'U' ) 
    438             CALL dom_vvl_interpol( e3t_n(:,:,:), e3v_n(:,:,:), 'V' ) 
    439             CALL dom_vvl_interpol( e3u_n(:,:,:), e3f_n(:,:,:), 'F' ) 
    440             ! Vertical scale factor interpolations 
    441             ! ------------------------------------ 
    442             CALL dom_vvl_interpol( e3t_n(:,:,:), e3w_n (:,:,:), 'W'  ) 
    443             CALL dom_vvl_interpol( e3u_n(:,:,:), e3uw_n(:,:,:), 'UW' ) 
    444             CALL dom_vvl_interpol( e3v_n(:,:,:), e3vw_n(:,:,:), 'VW' ) 
    445             CALL dom_vvl_interpol( e3u_b(:,:,:), e3uw_b(:,:,:), 'UW' ) 
    446             CALL dom_vvl_interpol( e3v_b(:,:,:), e3vw_b(:,:,:), 'VW' ) 
    447             ! t- and w- points depth 
    448             ! ---------------------- 
    449             !!gm not sure of that.... 
    450             gdept_n(:,:,1) = 0.5_wp * e3w_n(:,:,1) 
    451             gdepw_n(:,:,1) = 0.0_wp 
    452             gde3w_n(:,:,1) = gdept_n(:,:,1) - sshn(:,:) 
    453             DO jk = 2, jpk 
    454                gdept_n(:,:,jk) = gdept_n(:,:,jk-1) + e3w_n(:,:,jk  ) 
    455                gdepw_n(:,:,jk) = gdepw_n(:,:,jk-1) + e3t_n(:,:,jk-1) 
    456                gde3w_n(:,:,jk) = gdept_n(:,:,jk  ) - sshn (:,:) 
    457             END DO 
     420         IF( .NOT.ln_linssh ) THEN     ! modified the now and before vertical mesh and scale factors  
     421            ! 
     422            !                             !* BEFORE fields :  
     423            CALL ssh2e3_before               ! set:      hu , hv , r1_hu, r1_hv  
     424            !                                    !  e3t, e3w, e3u, e3uw, e3v, e3vw 
     425            ! 
     426            !                             !* NOW fields :  
     427            CALL ssh2e3_now                  ! set: ht , hu , hv , r1_hu, r1_hv 
     428            !                                !      e3t, e3w, e3u, e3uw, e3v, e3vw, e3f 
     429            !                                !      gdept_n, gdepw_n, gde3w_n 
    458430         ENDIF 
    459431      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.