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 13334 for NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/src/OCE/DOM/domvvl.F90 – NEMO

Ignore:
Timestamp:
2020-07-22T16:20:32+02:00 (4 years ago)
Author:
jchanut
Message:

finish bypassing ocean/ice initialization with AGRIF, #2222, #2129

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13312_AGRIF-03-04_jchanut_vinterp_tstep/src/OCE/DOM/domvvl.F90

    r13295 r13334  
    2525   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2626   USE timing          ! Timing 
     27 
     28   USE agrif_oce       ! initial state interpolation 
     29   USE agrif_oce_interp  
    2730 
    2831   IMPLICIT NONE 
     
    803806      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
    804807         !                                   ! =============== 
    805          IF( ln_rstart ) THEN                   !* Read the restart file 
    806             CALL rst_read_open                  !  open the restart file if necessary 
    807             CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm), ldxios = lrxios    ) 
    808             ! 
    809             id1 = iom_varid( numror, 'e3t_b', ldstop = .FALSE. ) 
    810             id2 = iom_varid( numror, 'e3t_n', ldstop = .FALSE. ) 
    811             id3 = iom_varid( numror, 'tilde_e3t_b', ldstop = .FALSE. ) 
    812             id4 = iom_varid( numror, 'tilde_e3t_n', ldstop = .FALSE. ) 
    813             id5 = iom_varid( numror, 'hdiv_lf', ldstop = .FALSE. ) 
    814             ! 
     808         IF( ln_rstart ) THEN 
     809                   !* Read the restart file 
     810#if defined key_agrif 
     811            IF ( (.NOT.Agrif_root()).AND.(ln_init_chfrpar) ) THEN 
     812               ! skip reading restart if initialized from parent: 
     813               id1 = -1 ; id2 = -1 ; id3 = -1 ; id4 = -1 ; id5 = -1 
     814            ELSE 
     815#endif 
     816               CALL rst_read_open                  !  open the restart file if necessary 
     817               CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm), ldxios = lrxios    ) 
     818               ! 
     819               id1 = iom_varid( numror, 'e3t_b', ldstop = .FALSE. ) 
     820               id2 = iom_varid( numror, 'e3t_n', ldstop = .FALSE. ) 
     821               id3 = iom_varid( numror, 'tilde_e3t_b', ldstop = .FALSE. ) 
     822               id4 = iom_varid( numror, 'tilde_e3t_n', ldstop = .FALSE. ) 
     823               id5 = iom_varid( numror, 'hdiv_lf', ldstop = .FALSE. ) 
     824#if defined key_agrif 
     825            ENDIF 
     826#endif 
    815827            !                             ! --------- ! 
    816828            !                             ! all cases ! 
     
    926938               ! is set up: 
    927939!               CALL usr_def_istate( gdept_0, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb), ssh(:,:,Kbb)  ) 
    928 !               ! 
     940               ! 
    929941!               DO jk=1,jpk 
    930942!                  e3t(:,:,jk,Kbb) =  e3t_0(:,:,jk) * ( ht_0(:,:) + ssh(:,:,Kbb) ) & 
    931 !                     &            / ( ht_0(:,:) + 1._wp -ssmask(:,:) ) * tmask(:,:,jk) 
     943!                     &                             / ( ht_0(:,:) + 1._wp -ssmask(:,:) ) * tmask(:,:,jk) & 
     944!                     &             + e3t_0(:,:,jk) * ( 1._wp - tmask(:,:,jk) ) 
    932945!               END DO 
    933946!               e3t(:,:,:,Kmm) = e3t(:,:,:,Kbb) 
    934                 ssh(:,:,Kmm)=0._wp 
    935                 e3t(:,:,:,Kmm)=e3t_0(:,:,:) 
    936                 e3t(:,:,:,Kbb)=e3t_0(:,:,:) 
     947               ssh(:,:,Kmm)=0._wp 
     948               e3t(:,:,:,Kmm)=e3t_0(:,:,:) 
     949               e3t(:,:,:,Kbb)=e3t_0(:,:,:) 
    937950               ! 
    938951            END IF           ! end of ll_wd edits 
     
    944957            END IF 
    945958         ENDIF 
     959 
     960#if defined key_agrif 
     961         IF ( .NOT.Agrif_root().AND.(ln_init_chfrpar) ) THEN 
     962            ! Interpolate initial ssh from parent: 
     963            CALL Agrif_istate_ssh( Kbb, Kmm ) 
     964            ! 
     965            DO jk = 1, jpk 
     966               e3t(:,:,jk,Kmm) =  e3t_0(:,:,jk) * ( ht_0(:,:) + ssh(:,:,Kmm)  ) & 
     967                 &                              / ( ht_0(:,:) + 1._wp - ssmask(:,:) ) * tmask(:,:,jk)   & 
     968                 &              + e3t_0(:,:,jk) * ( 1._wp - tmask(:,:,jk) ) 
     969            END DO 
     970            e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm) 
     971         ENDIF 
     972#endif 
    946973         ! 
    947974      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
Note: See TracChangeset for help on using the changeset viewer.