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 12246 for NEMO/branches/2019/dev_r12072_MERGE_OPTION2_2019/src/OCE/BDY/bdydta.F90 – NEMO

Ignore:
Timestamp:
2019-12-13T16:11:51+01:00 (4 years ago)
Author:
smasson
Message:

rev12232_dev_r12072_MERGE_OPTION2_2019: add modifications from dev_r12114_ticket_2263, results unchanged except SPITZ12 as explained in #2263

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r12072_MERGE_OPTION2_2019/src/OCE/BDY/bdydta.F90

    r12202 r12246  
    7575CONTAINS 
    7676 
    77    SUBROUTINE bdy_dta( kt, kt_offset ) 
     77   SUBROUTINE bdy_dta( kt, pt_offset ) 
    7878      !!---------------------------------------------------------------------- 
    7979      !!                   ***  SUBROUTINE bdy_dta  *** 
     
    8585      !!---------------------------------------------------------------------- 
    8686      INTEGER, INTENT(in)           ::   kt           ! ocean time-step index  
    87       INTEGER, INTENT(in), OPTIONAL ::   kt_offset    ! time offset in units of timesteps 
    88       !                                               ! kt_offset = 0 => get data at "now" time level 
    89       !                                               ! kt_offset = -1 => get data at "before" time level 
    90       !                                               ! kt_offset = +1 => get data at "after" time level 
    91       !                                               ! etc. 
     87      REAL(wp),INTENT(in), OPTIONAL ::   pt_offset    ! time offset in units of timesteps 
    9288      ! 
    9389      INTEGER ::  jbdy, jfld, jstart, jend, ib, jl    ! dummy loop indices 
     
    214210         ! read/update all bdy data 
    215211         ! ------------------------ 
    216          CALL fld_read( kt, 1, bf_alias, kt_offset = kt_offset ) 
     212         CALL fld_read( kt, 1, bf_alias, pt_offset = pt_offset ) 
    217213 
    218214         ! apply some corrections in some specific cases... 
     
    335331                  nblen => idx_bdy(jbdy)%nblen 
    336332                  nblenrim => idx_bdy(jbdy)%nblenrim 
    337                   IF( cn_dyn2d(jbdy) == 'frs' ) THEN ; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
    338                      IF ( dta_bdy(jbdy)%lneed_ssh   ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 
    339                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 
    340                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 
    341                   ENDIF 
    342                END DO 
    343             ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
    344                ! 
    345                CALL bdy_dta_tides( kt=kt, kt_offset=kt_offset ) 
    346             ENDIF 
     333                  IF( cn_dyn2d(jbdy) == 'frs' ) THEN   ;   ilen1(:)=nblen(:) 
     334                  ELSE                                 ;   ilen1(:)=nblenrim(:) 
     335                  ENDIF 
     336                  IF ( dta_bdy(jbdy)%lneed_ssh   ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 
     337                  IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 
     338                  IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 
     339               ENDIF 
     340            END DO 
     341         ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
     342            ! 
     343            CALL bdy_dta_tides( kt=kt, pt_offset=pt_offset ) 
    347344         ENDIF 
    348          ! 
    349          IF( ln_timing )   CALL timing_stop('bdy_dta') 
    350          ! 
    351       END SUBROUTINE bdy_dta 
     345      ENDIF 
     346      ! 
     347      IF( ln_timing )   CALL timing_stop('bdy_dta') 
     348      ! 
     349   END SUBROUTINE bdy_dta 
    352350 
    353351 
     
    448446            IF( nn_ice_dta(jbdy) == 1 ) THEN   ! if we get ice bdy data from netcdf file 
    449447               CALL fld_fill(  bf(jp_bdya_i,jbdy:jbdy), bn_a_i, cn_dir, 'bdy_dta', 'a_i'//' '//ctmp1, ctmp2 )   ! use namelist info 
    450                CALL fld_clopn( bf(jp_bdya_i,jbdy), nyear, nmonth, nday )   ! not a problem when we call it again after 
     448               CALL fld_def( bf(jp_bdya_i,jbdy) ) 
     449               CALL iom_open( bf(jp_bdya_i,jbdy)%clname, bf(jp_bdya_i,jbdy)%num ) 
    451450               idvar = iom_varid( bf(jp_bdya_i,jbdy)%num, bf(jp_bdya_i,jbdy)%clvar, kndims=indims, kdimsz=i4dimsz, lduld=lluld ) 
    452451               IF( indims == 4 .OR. ( indims == 3 .AND. .NOT. lluld ) ) THEN   ;   ipl = i4dimsz(3)   ! xylt or xyl 
    453452               ELSE                                                            ;   ipl = 1            ! xy or xyt 
    454453               ENDIF 
     454               CALL iom_close( bf(jp_bdya_i,jbdy)%num ) 
    455455               bf(jp_bdya_i,jbdy)%clrootname = 'NOT USED'   ! reset to default value as this subdomain may not need to read this bdy 
    456456            ENDIF 
Note: See TracChangeset for help on using the changeset viewer.