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 12955 for NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/BDY/bdydta.F90 – NEMO

Ignore:
Timestamp:
2020-05-20T16:08:51+02:00 (4 years ago)
Author:
smasson
Message:

Clem's branch: merge with trunk@12926

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/BDY/bdydta.F90

    r12744 r12955  
    9696      INTEGER ::  jbdy, jfld, jstart, jend, ib, jl    ! dummy loop indices 
    9797      INTEGER ::  ii, ij, ik, igrd, ipl               ! local integers 
    98       INTEGER,   DIMENSION(jpbgrd)     ::   ilen1  
    9998      TYPE(OBC_DATA)         , POINTER ::   dta_alias        ! short cut 
    10099      TYPE(FLD), DIMENSION(:), POINTER ::   bf_alias 
     
    121120                  END DO 
    122121               ENDIF 
    123                IF( dta_bdy(jbdy)%lneed_dyn2d .AND. ASSOCIATED(dta_bdy(jbdy)%u2d) ) THEN   ! no SIZE with a unassociated pointer 
     122               IF( ASSOCIATED(dta_bdy(jbdy)%u2d) ) THEN   ! no SIZE with a unassociated pointer. v2d and u2d can differ on subdomain 
    124123                  igrd = 2 
    125                   DO ib = 1, SIZE(dta_bdy(jbdy)%u2d)   ! u2d is used only on the rim except if ln_full_vel = T, see bdy_dta_init 
     124                  DO ib = 1, SIZE(dta_bdy(jbdy)%u2d)      ! u2d is used either over the whole bdy or only on the rim 
    126125                     ii = idx_bdy(jbdy)%nbi(ib,igrd) 
    127126                     ij = idx_bdy(jbdy)%nbj(ib,igrd) 
    128127                     dta_bdy(jbdy)%u2d(ib) = un_b(ii,ij) * umask(ii,ij,1)          
    129128                  END DO 
     129               ENDIF 
     130               IF( ASSOCIATED(dta_bdy(jbdy)%v2d) ) THEN   ! no SIZE with a unassociated pointer. v2d and u2d can differ on subdomain 
    130131                  igrd = 3 
    131                   DO ib = 1, SIZE(dta_bdy(jbdy)%v2d)   ! v2d is used only on the rim except if ln_full_vel = T, see bdy_dta_init 
     132                  DO ib = 1, SIZE(dta_bdy(jbdy)%v2d)      ! v2d is used either over the whole bdy or only on the rim 
    132133                     ii = idx_bdy(jbdy)%nbi(ib,igrd) 
    133134                     ij = idx_bdy(jbdy)%nbj(ib,igrd) 
     
    216217         ! 
    217218         ! if runoff condition: change river flow we read (in m3/s) into barotropic velocity (m/s) 
    218          IF( cn_tra(jbdy) == 'runoff' .AND. TRIM(bf_alias(jp_bdyu2d)%clrootname) /= 'NOT USED' ) THEN   ! runoff and we read u/v2d 
     219         IF( cn_tra(jbdy) == 'runoff' ) THEN   ! runoff 
    219220            ! 
    220             igrd = 2                      ! zonal flow (m3/s) to barotropic zonal velocity (m/s) 
    221             DO ib = 1, idx_bdy(jbdy)%nblen(igrd) 
    222                ii   = idx_bdy(jbdy)%nbi(ib,igrd) 
    223                ij   = idx_bdy(jbdy)%nbj(ib,igrd) 
    224                dta_alias%u2d(ib) = dta_alias%u2d(ib) / ( e2u(ii,ij) * hu_0(ii,ij) ) 
    225             END DO 
    226             igrd = 3                      ! meridional flow (m3/s) to barotropic meridional velocity (m/s) 
    227             DO ib = 1, idx_bdy(jbdy)%nblen(igrd) 
    228                ii   = idx_bdy(jbdy)%nbi(ib,igrd) 
    229                ij   = idx_bdy(jbdy)%nbj(ib,igrd) 
    230                dta_alias%v2d(ib) = dta_alias%v2d(ib) / ( e1v(ii,ij) * hv_0(ii,ij) ) 
    231             END DO 
     221            IF( ASSOCIATED(dta_bdy(jbdy)%u2d) ) THEN   ! no SIZE with a unassociated pointer. v2d and u2d can differ on subdomain 
     222               igrd = 2                         ! zonal flow (m3/s) to barotropic zonal velocity (m/s) 
     223               DO ib = 1, SIZE(dta_alias%u2d)   ! u2d is used either over the whole bdy or only on the rim 
     224                  ii   = idx_bdy(jbdy)%nbi(ib,igrd) 
     225                  ij   = idx_bdy(jbdy)%nbj(ib,igrd) 
     226                  dta_alias%u2d(ib) = dta_alias%u2d(ib) / ( e2u(ii,ij) * hu_0(ii,ij) ) 
     227               END DO 
     228            ENDIF 
     229            IF( ASSOCIATED(dta_bdy(jbdy)%v2d) ) THEN   ! no SIZE with a unassociated pointer. v2d and u2d can differ on subdomain 
     230               igrd = 3                         ! meridional flow (m3/s) to barotropic meridional velocity (m/s) 
     231               DO ib = 1, SIZE(dta_alias%v2d)   ! v2d is used either over the whole bdy or only on the rim 
     232                  ii   = idx_bdy(jbdy)%nbi(ib,igrd) 
     233                  ij   = idx_bdy(jbdy)%nbj(ib,igrd) 
     234                  dta_alias%v2d(ib) = dta_alias%v2d(ib) / ( e1v(ii,ij) * hv_0(ii,ij) ) 
     235               END DO 
     236            ENDIF 
    232237         ENDIF 
    233238 
    234239         ! tidal harmonic forcing ONLY: initialise arrays 
    235240         IF( nn_dyn2d_dta(jbdy) == 2 ) THEN   ! we did not read ssh, u/v2d  
    236             IF( dta_alias%lneed_ssh   .AND. ASSOCIATED(dta_alias%ssh) ) dta_alias%ssh(:) = 0._wp 
    237             IF( dta_alias%lneed_dyn2d .AND. ASSOCIATED(dta_alias%u2d) ) dta_alias%u2d(:) = 0._wp 
    238             IF( dta_alias%lneed_dyn2d .AND. ASSOCIATED(dta_alias%v2d) ) dta_alias%v2d(:) = 0._wp 
     241            IF( ASSOCIATED(dta_alias%ssh) ) dta_alias%ssh(:) = 0._wp 
     242            IF( ASSOCIATED(dta_alias%u2d) ) dta_alias%u2d(:) = 0._wp 
     243            IF( ASSOCIATED(dta_alias%v2d) ) dta_alias%v2d(:) = 0._wp 
    239244         ENDIF 
    240245 
     
    347352            DO jbdy = 1, nb_bdy      ! Tidal component added in ts loop 
    348353               IF ( nn_dyn2d_dta(jbdy) .GE. 2 ) THEN 
    349                   IF( cn_dyn2d(jbdy) == 'frs' ) THEN   ;   ilen1(:)=idx_bdy(jbdy)%nblen(:) 
    350                   ELSE                                 ;   ilen1(:)=idx_bdy(jbdy)%nblenrim(:) 
    351                   ENDIF 
    352                      IF ( dta_bdy(jbdy)%lneed_ssh   ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 
    353                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 
    354                      IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 
    355                   ENDIF 
    356                END DO 
    357             ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
    358                ! 
    359                CALL bdy_dta_tides( kt=kt, kt_offset=kt_offset ) 
    360             ENDIF 
    361          ENDIF 
    362          ! 
    363          IF( ln_timing )   CALL timing_stop('bdy_dta') 
    364          ! 
    365       END SUBROUTINE bdy_dta 
    366  
     354                  IF( ASSOCIATED(dta_bdy(jbdy)%ssh) ) dta_bdy_s(jbdy)%ssh(:) = dta_bdy(jbdy)%ssh(:) 
     355                  IF( ASSOCIATED(dta_bdy(jbdy)%u2d) ) dta_bdy_s(jbdy)%u2d(:) = dta_bdy(jbdy)%u2d(:) 
     356                  IF( ASSOCIATED(dta_bdy(jbdy)%v2d) ) dta_bdy_s(jbdy)%v2d(:) = dta_bdy(jbdy)%v2d(:) 
     357               ENDIF 
     358            END DO 
     359         ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
     360            ! 
     361            CALL bdy_dta_tides( kt=kt, kt_offset=kt_offset ) 
     362         ENDIF 
     363      ENDIF 
     364      ! 
     365      IF( ln_timing )   CALL timing_stop('bdy_dta') 
     366      ! 
     367   END SUBROUTINE bdy_dta 
     368    
    367369 
    368370   SUBROUTINE bdy_dta_init 
     
    394396      LOGICAL                                ::   llneed        ! 
    395397      LOGICAL                                ::   llread        ! 
     398      LOGICAL                                ::   llfullbdy     ! 
    396399      TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_tem, bn_sal, bn_u3d, bn_v3d   ! must be an array to be used with fld_fill 
    397400      TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_ssh, bn_u2d, bn_v2d           ! informations about the fields to be read 
     
    498501               igrd = 2                                                    ! U point 
    499502               ipk = 1                                                     ! surface data 
    500                llneed = dta_bdy(jbdy)%lneed_dyn2d                          ! dta_bdy(jbdy)%ssh will be needed 
     503               llneed = dta_bdy(jbdy)%lneed_dyn2d                          ! dta_bdy(jbdy)%u2d will be needed 
    501504               llread = .NOT. ln_full_vel .AND. MOD(nn_dyn2d_dta(jbdy),2) == 1   ! don't get u2d from u3d and read NetCDF file 
    502505               bf_alias => bf(jp_bdyu2d,jbdy:jbdy)                         ! alias for u2d structure of bdy number jbdy 
    503506               bn_alias => bn_u2d                                          ! alias for u2d structure of nambdy_dta 
    504                IF( ln_full_vel ) THEN  ;   iszdim = idx_bdy(jbdy)%nblen(igrd)      ! will be computed from u3d -> need on the full bdy 
    505                ELSE                    ;   iszdim = idx_bdy(jbdy)%nblenrim(igrd)   ! used only on the rim 
     507               llfullbdy = ln_full_vel .OR. cn_dyn2d(jbdy) == 'frs'        ! need u2d over the whole bdy or only over the rim? 
     508               IF( llfullbdy ) THEN  ;   iszdim = idx_bdy(jbdy)%nblen(igrd) 
     509               ELSE                  ;   iszdim = idx_bdy(jbdy)%nblenrim(igrd) 
    506510               ENDIF 
    507511            ENDIF 
     
    510514               igrd = 3                                                    ! V point 
    511515               ipk = 1                                                     ! surface data 
    512                llneed = dta_bdy(jbdy)%lneed_dyn2d                          ! dta_bdy(jbdy)%ssh will be needed 
     516               llneed = dta_bdy(jbdy)%lneed_dyn2d                          ! dta_bdy(jbdy)%v2d will be needed 
    513517               llread = .NOT. ln_full_vel .AND. MOD(nn_dyn2d_dta(jbdy),2) == 1   ! don't get v2d from v3d and read NetCDF file 
    514518               bf_alias => bf(jp_bdyv2d,jbdy:jbdy)                         ! alias for v2d structure of bdy number jbdy 
    515519               bn_alias => bn_v2d                                          ! alias for v2d structure of nambdy_dta  
    516                IF( ln_full_vel ) THEN  ;   iszdim = idx_bdy(jbdy)%nblen(igrd)      ! will be computed from v3d -> need on the full bdy 
    517                ELSE                    ;   iszdim = idx_bdy(jbdy)%nblenrim(igrd)   ! used only on the rim 
     520               llfullbdy = ln_full_vel .OR. cn_dyn2d(jbdy) == 'frs'        ! need v2d over the whole bdy or only over the rim? 
     521               IF( llfullbdy ) THEN  ;   iszdim = idx_bdy(jbdy)%nblen(igrd) 
     522               ELSE                  ;   iszdim = idx_bdy(jbdy)%nblenrim(igrd) 
    518523               ENDIF 
    519524            ENDIF 
Note: See TracChangeset for help on using the changeset viewer.