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 – NEMO

Changeset 12955 for NEMO/branches


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

Clem's branch: merge with trunk@12926

Location:
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl
Files:
16 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/NST/agrif_oce_interp.F90

    r12816 r12955  
    9696      i1 =  1   ;   i2 = nlci 
    9797      j1 =  1   ;   j2 = nlcj 
    98       IF( l_Northedge )   j1 = 2 + nbghostcells 
    99       IF( l_Southedge )   j2 = nlcj - nbghostcells - 1 
     98      IF( l_Southedge )   j1 = 2 + nbghostcells 
     99      IF( l_Northedge )   j2 = nlcj - nbghostcells - 1 
    100100      IF( l_Westedge )    i1 = 2 + nbghostcells  
    101101      IF( l_Eastedge )    i2 = nlci - nbghostcells - 1 
  • 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 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/BDY/bdytides.F90

    r11536 r12955  
    6262      !! namelist variables 
    6363      !!------------------- 
    64       CHARACTER(len=80)                         ::   filtide             !: Filename root for tidal input files 
    65       LOGICAL                                   ::   ln_bdytide_2ddta    !: If true, read 2d harmonic data 
    66       LOGICAL                                   ::   ln_bdytide_conj     !: If true, assume complex conjugate tidal data 
     64      CHARACTER(len=80)                         ::   filtide             ! Filename root for tidal input files 
     65      LOGICAL                                   ::   ln_bdytide_2ddta    ! If true, read 2d harmonic data 
     66      LOGICAL                                   ::   ln_bdytide_conj     ! If true, assume complex conjugate tidal data 
    6767      !! 
    68       INTEGER                                   ::   ib_bdy, itide, ib   !: dummy loop indices 
    69       INTEGER                                   ::   ii, ij              !: dummy loop indices 
     68      INTEGER                                   ::   ib_bdy, itide, ib   ! dummy loop indices 
     69      INTEGER                                   ::   ii, ij              ! dummy loop indices 
    7070      INTEGER                                   ::   inum, igrd 
    71       INTEGER, DIMENSION(3)                     ::   ilen0       !: length of boundary data (from OBC arrays) 
     71      INTEGER                                   ::   isz                 ! bdy data size 
    7272      INTEGER                                   ::   ios                 ! Local integer output status for namelist read 
    73       CHARACTER(len=80)                         ::   clfile              !: full file name for tidal input file  
    74       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)    ::   dta_read            !: work space to read in tidal harmonics data 
    75       REAL(wp),ALLOCATABLE, DIMENSION(:,:)      ::   ztr, zti            !:  "     "    "   "   "   "        "      "  
     73      CHARACTER(len=80)                         ::   clfile              ! full file name for tidal input file  
     74      REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)    ::   dta_read            ! work space to read in tidal harmonics data 
     75      REAL(wp),ALLOCATABLE, DIMENSION(:,:)      ::   ztr, zti            !  "     "    "   "   "   "        "      "  
    7676      !! 
    77       TYPE(TIDES_DATA),  POINTER                ::   td                  !: local short cut    
     77      TYPE(TIDES_DATA), POINTER                 ::   td                  ! local short cut    
     78      TYPE(  OBC_DATA), POINTER                 ::   dta                 ! local short cut 
    7879      !! 
    7980      NAMELIST/nambdy_tide/filtide, ln_bdytide_2ddta, ln_bdytide_conj 
     
    8990         IF( nn_dyn2d_dta(ib_bdy) >= 2 ) THEN 
    9091            ! 
    91             td => tides(ib_bdy) 
    92  
     92            td  => tides(ib_bdy) 
     93            dta => dta_bdy(ib_bdy) 
     94          
    9395            ! Namelist nambdy_tide : tidal harmonic forcing at open boundaries 
    9496            filtide(:) = '' 
     
    115117            IF(lwp) WRITE(numout,*) ' ' 
    116118 
    117             ! Allocate space for tidal harmonics data - get size from OBC data arrays 
     119            ! Allocate space for tidal harmonics data - get size from BDY data arrays 
     120            ! Allocate also slow varying data in the case of time splitting: 
     121            ! Do it anyway because at this stage knowledge of free surface scheme is unknown 
    118122            ! ----------------------------------------------------------------------- 
    119  
    120             ! JC: If FRS scheme is used, we assume that tidal is needed over the whole 
    121             ! relaxation area       
    122             IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN   ;   ilen0(:) = idx_bdy(ib_bdy)%nblen   (:) 
    123             ELSE                                   ;   ilen0(:) = idx_bdy(ib_bdy)%nblenrim(:) 
     123            IF( ASSOCIATED(dta%ssh) ) THEN   ! we use bdy ssh on this mpi subdomain 
     124               isz = SIZE(dta%ssh) 
     125               ALLOCATE( td%ssh0( isz, nb_harmo, 2 ), td%ssh( isz, nb_harmo, 2 ), dta_bdy_s(ib_bdy)%ssh( isz ) ) 
     126               dta_bdy_s(ib_bdy)%ssh(:) = 0._wp   ! needed? 
    124127            ENDIF 
    125  
    126             ALLOCATE( td%ssh0( ilen0(1), nb_harmo, 2 ) ) 
    127             ALLOCATE( td%ssh ( ilen0(1), nb_harmo, 2 ) ) 
    128  
    129             ALLOCATE( td%u0( ilen0(2), nb_harmo, 2 ) ) 
    130             ALLOCATE( td%u ( ilen0(2), nb_harmo, 2 ) ) 
    131  
    132             ALLOCATE( td%v0( ilen0(3), nb_harmo, 2 ) ) 
    133             ALLOCATE( td%v ( ilen0(3), nb_harmo, 2 ) ) 
    134  
    135             td%ssh0(:,:,:) = 0._wp 
    136             td%ssh (:,:,:) = 0._wp 
    137             td%u0  (:,:,:) = 0._wp 
    138             td%u   (:,:,:) = 0._wp 
    139             td%v0  (:,:,:) = 0._wp 
    140             td%v   (:,:,:) = 0._wp 
    141  
     128            IF( ASSOCIATED(dta%u2d) ) THEN   ! we use bdy u2d on this mpi subdomain 
     129               isz = SIZE(dta%u2d) 
     130               ALLOCATE( td%u0  ( isz, nb_harmo, 2 ), td%u  ( isz, nb_harmo, 2 ), dta_bdy_s(ib_bdy)%u2d( isz ) ) 
     131               dta_bdy_s(ib_bdy)%u2d(:) = 0._wp   ! needed? 
     132            ENDIF 
     133            IF( ASSOCIATED(dta%v2d) ) THEN   ! we use bdy v2d on this mpi subdomain 
     134               isz = SIZE(dta%v2d) 
     135               ALLOCATE( td%v0  ( isz, nb_harmo, 2 ), td%v  ( isz, nb_harmo, 2 ), dta_bdy_s(ib_bdy)%v2d( isz ) ) 
     136               dta_bdy_s(ib_bdy)%v2d(:) = 0._wp   ! needed? 
     137            ENDIF 
     138 
     139            ! fill td%ssh0, td%u0, td%v0 
     140            ! ----------------------------------------------------------------------- 
    142141            IF( ln_bdytide_2ddta ) THEN 
     142               ! 
    143143               ! It is assumed that each data file contains all complex harmonic amplitudes 
    144144               ! given on the global domain (ie global, jpiglo x jpjglo) 
     
    147147               ! 
    148148               ! SSH fields 
    149                clfile = TRIM(filtide)//'_grid_T.nc' 
    150                CALL iom_open( clfile , inum )  
    151                igrd = 1                       ! Everything is at T-points here 
    152                DO itide = 1, nb_harmo 
    153                   CALL iom_get( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_z1', ztr(:,:) ) 
    154                   CALL iom_get( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_z2', zti(:,:) )  
    155                   DO ib = 1, ilen0(igrd) 
    156                      ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
    157                      ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
    158                      IF( ii == 1 .OR. ii == jpi .OR. ij == 1 .OR. ij == jpj )  CYCLE   ! to remove? 
    159                      td%ssh0(ib,itide,1) = ztr(ii,ij) 
    160                      td%ssh0(ib,itide,2) = zti(ii,ij) 
     149               IF( ASSOCIATED(dta%ssh) ) THEN   ! we use bdy ssh on this mpi subdomain 
     150                  clfile = TRIM(filtide)//'_grid_T.nc' 
     151                  CALL iom_open( clfile , inum )  
     152                  igrd = 1                       ! Everything is at T-points here 
     153                  DO itide = 1, nb_harmo 
     154                     CALL iom_get( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_z1', ztr(:,:) ) 
     155                     CALL iom_get( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_z2', zti(:,:) )  
     156                     DO ib = 1, SIZE(dta%ssh) 
     157                        ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
     158                        ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
     159                        td%ssh0(ib,itide,1) = ztr(ii,ij) 
     160                        td%ssh0(ib,itide,2) = zti(ii,ij) 
     161                     END DO 
    161162                  END DO 
    162                END DO  
    163                CALL iom_close( inum ) 
     163                  CALL iom_close( inum ) 
     164               END IF 
    164165               ! 
    165166               ! U fields 
    166                clfile = TRIM(filtide)//'_grid_U.nc' 
    167                CALL iom_open( clfile , inum )  
    168                igrd = 2                       ! Everything is at U-points here 
    169                DO itide = 1, nb_harmo 
    170                   CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_u1', ztr(:,:) ) 
    171                   CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_u2', zti(:,:) ) 
    172                   DO ib = 1, ilen0(igrd) 
    173                      ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
    174                      ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
    175                      IF( ii == 1 .OR. ii == jpi .OR. ij == 1 .OR. ij == jpj )  CYCLE   ! to remove? 
    176                      td%u0(ib,itide,1) = ztr(ii,ij) 
    177                      td%u0(ib,itide,2) = zti(ii,ij) 
     167               IF( ASSOCIATED(dta%u2d) ) THEN   ! we use bdy u2d on this mpi subdomain 
     168                  clfile = TRIM(filtide)//'_grid_U.nc' 
     169                  CALL iom_open( clfile , inum )  
     170                  igrd = 2                       ! Everything is at U-points here 
     171                  DO itide = 1, nb_harmo 
     172                     CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_u1', ztr(:,:) ) 
     173                     CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_u2', zti(:,:) ) 
     174                     DO ib = 1, SIZE(dta%u2d) 
     175                        ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
     176                        ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
     177                        td%u0(ib,itide,1) = ztr(ii,ij) 
     178                        td%u0(ib,itide,2) = zti(ii,ij) 
     179                     END DO 
    178180                  END DO 
    179                END DO 
    180                CALL iom_close( inum ) 
     181                  CALL iom_close( inum ) 
     182               END IF 
    181183               ! 
    182184               ! V fields 
    183                clfile = TRIM(filtide)//'_grid_V.nc' 
    184                CALL iom_open( clfile , inum )  
    185                igrd = 3                       ! Everything is at V-points here 
    186                DO itide = 1, nb_harmo 
    187                   CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_v1', ztr(:,:) ) 
    188                   CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_v2', zti(:,:) ) 
    189                   DO ib = 1, ilen0(igrd) 
    190                      ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
    191                      ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
    192                      IF( ii == 1 .OR. ii == jpi .OR. ij == 1 .OR. ij == jpj )  CYCLE   ! to remove? 
    193                      td%v0(ib,itide,1) = ztr(ii,ij) 
    194                      td%v0(ib,itide,2) = zti(ii,ij) 
     185               IF( ASSOCIATED(dta%v2d) ) THEN   ! we use bdy v2d on this mpi subdomain 
     186                  clfile = TRIM(filtide)//'_grid_V.nc' 
     187                  CALL iom_open( clfile , inum )  
     188                  igrd = 3                       ! Everything is at V-points here 
     189                  DO itide = 1, nb_harmo 
     190                     CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_v1', ztr(:,:) ) 
     191                     CALL iom_get  ( inum, jpdom_autoglo, TRIM(Wave(ntide(itide))%cname_tide)//'_v2', zti(:,:) ) 
     192                     DO ib = 1, SIZE(dta%v2d) 
     193                        ii = idx_bdy(ib_bdy)%nbi(ib,igrd) 
     194                        ij = idx_bdy(ib_bdy)%nbj(ib,igrd) 
     195                        td%v0(ib,itide,1) = ztr(ii,ij) 
     196                        td%v0(ib,itide,2) = zti(ii,ij) 
     197                     END DO 
    195198                  END DO 
    196                END DO   
    197                CALL iom_close( inum ) 
     199                  CALL iom_close( inum ) 
     200               END IF 
    198201               ! 
    199202               DEALLOCATE( ztr, zti )  
     
    203206               ! Read tidal data only on bdy segments 
    204207               !  
    205                ALLOCATE( dta_read( MAXVAL(ilen0(1:3)), 1, 1 ) ) 
     208               ALLOCATE( dta_read( MAXVAL( idx_bdy(ib_bdy)%nblen(:) ), 1, 1 ) ) 
    206209               ! 
    207210               ! Open files and read in tidal forcing data 
     
    210213               DO itide = 1, nb_harmo 
    211214                  !                                                              ! SSH fields 
    212                   clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_T.nc' 
    213                   CALL iom_open( clfile, inum ) 
    214                   CALL fld_map( inum, 'z1' , dta_read(1:ilen0(1),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,1) ) 
    215                   td%ssh0(:,itide,1) = dta_read(1:ilen0(1),1,1) 
    216                   CALL fld_map( inum, 'z2' , dta_read(1:ilen0(1),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,1) ) 
    217                   td%ssh0(:,itide,2) = dta_read(1:ilen0(1),1,1) 
    218                   CALL iom_close( inum ) 
     215                  IF( ASSOCIATED(dta%ssh) ) THEN   ! we use bdy ssh on this mpi subdomain 
     216                     isz = SIZE(dta%ssh) 
     217                     clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_T.nc' 
     218                     CALL iom_open( clfile, inum ) 
     219                     CALL fld_map( inum, 'z1', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,1) ) 
     220                     td%ssh0(:,itide,1) = dta_read(1:isz,1,1) 
     221                     CALL fld_map( inum, 'z2', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,1) ) 
     222                     td%ssh0(:,itide,2) = dta_read(1:isz,1,1) 
     223                     CALL iom_close( inum ) 
     224                  ENDIF 
    219225                  !                                                              ! U fields 
    220                   clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_U.nc' 
    221                   CALL iom_open( clfile, inum ) 
    222                   CALL fld_map( inum, 'u1' , dta_read(1:ilen0(2),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,2) ) 
    223                   td%u0(:,itide,1) = dta_read(1:ilen0(2),1,1) 
    224                   CALL fld_map( inum, 'u2' , dta_read(1:ilen0(2),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,2) ) 
    225                   td%u0(:,itide,2) = dta_read(1:ilen0(2),1,1) 
    226                   CALL iom_close( inum ) 
     226                  IF( ASSOCIATED(dta%u2d) ) THEN   ! we use bdy u2d on this mpi subdomain 
     227                     isz = SIZE(dta%u2d) 
     228                     clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_U.nc' 
     229                     CALL iom_open( clfile, inum ) 
     230                     CALL fld_map( inum, 'u1', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,2) ) 
     231                     td%u0(:,itide,1) = dta_read(1:isz,1,1) 
     232                     CALL fld_map( inum, 'u2', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,2) ) 
     233                     td%u0(:,itide,2) = dta_read(1:isz,1,1) 
     234                     CALL iom_close( inum ) 
     235                  ENDIF 
    227236                  !                                                              ! V fields 
    228                   clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_V.nc' 
    229                   CALL iom_open( clfile, inum ) 
    230                   CALL fld_map( inum, 'v1' , dta_read(1:ilen0(3),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,3) ) 
    231                   td%v0(:,itide,1) = dta_read(1:ilen0(3),1,1) 
    232                   CALL fld_map( inum, 'v2' , dta_read(1:ilen0(3),1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,3) ) 
    233                   td%v0(:,itide,2) = dta_read(1:ilen0(3),1,1) 
    234                   CALL iom_close( inum ) 
     237                  IF( ASSOCIATED(dta%v2d) ) THEN   ! we use bdy v2d on this mpi subdomain 
     238                     isz = SIZE(dta%v2d) 
     239                     clfile = TRIM(filtide)//TRIM(Wave(ntide(itide))%cname_tide)//'_grid_V.nc' 
     240                     CALL iom_open( clfile, inum ) 
     241                     CALL fld_map( inum, 'v1', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,3) ) 
     242                     td%v0(:,itide,1) = dta_read(1:isz,1,1) 
     243                     CALL fld_map( inum, 'v2', dta_read(1:isz,1:1,1:1) , 1, idx_bdy(ib_bdy)%nbmap(:,3) ) 
     244                     td%v0(:,itide,2) = dta_read(1:isz,1,1) 
     245                     CALL iom_close( inum ) 
     246                  ENDIF 
    235247                  ! 
    236248               END DO ! end loop on tidal components 
     
    241253            ! 
    242254            IF( ln_bdytide_conj ) THEN    ! assume complex conjugate in data files 
    243                td%ssh0(:,:,2) = - td%ssh0(:,:,2) 
    244                td%u0  (:,:,2) = - td%u0  (:,:,2) 
    245                td%v0  (:,:,2) = - td%v0  (:,:,2) 
     255               IF( ASSOCIATED(dta%ssh) )   td%ssh0(:,:,2) = - td%ssh0(:,:,2) 
     256               IF( ASSOCIATED(dta%u2d) )   td%u0  (:,:,2) = - td%u0  (:,:,2) 
     257               IF( ASSOCIATED(dta%v2d) )   td%v0  (:,:,2) = - td%v0  (:,:,2) 
    246258            ENDIF 
    247             ! 
    248             ! Allocate slow varying data in the case of time splitting: 
    249             ! Do it anyway because at this stage knowledge of free surface scheme is unknown 
    250             ALLOCATE( dta_bdy_s(ib_bdy)%ssh ( ilen0(1) ) ) 
    251             ALLOCATE( dta_bdy_s(ib_bdy)%u2d ( ilen0(2) ) ) 
    252             ALLOCATE( dta_bdy_s(ib_bdy)%v2d ( ilen0(3) ) ) 
    253             dta_bdy_s(ib_bdy)%ssh(:) = 0._wp 
    254             dta_bdy_s(ib_bdy)%u2d(:) = 0._wp 
    255             dta_bdy_s(ib_bdy)%v2d(:) = 0._wp 
    256259            ! 
    257260         ENDIF ! nn_dyn2d_dta(ib_bdy) >= 2 
     
    281284      !                                                 ! etc. 
    282285      ! 
    283       INTEGER  ::   itide, igrd, ib       ! dummy loop indices 
     286      INTEGER  ::   itide, ib             ! dummy loop indices 
    284287      INTEGER  ::   time_add              ! time offset in units of timesteps 
    285       INTEGER, DIMENSION(3) ::   ilen0    ! length of boundary data (from OBC arrays) 
     288      INTEGER  ::   isz                   ! bdy data size 
    286289      REAL(wp) ::   z_arg, z_sarg, zflag, zramp   ! local scalars     
    287290      REAL(wp), DIMENSION(jpmax_harmo) :: z_sist, z_cost 
    288291      !!---------------------------------------------------------------------- 
    289292      ! 
    290       ilen0(1) =  SIZE(td%ssh(:,1,1)) 
    291       ilen0(2) =  SIZE(td%u(:,1,1)) 
    292       ilen0(3) =  SIZE(td%v(:,1,1)) 
    293  
    294293      zflag=1 
    295294      IF ( PRESENT(kit) ) THEN 
    296295        IF ( kit /= 1 ) zflag=0 
    297296      ENDIF 
    298  
     297      ! 
    299298      IF ( (nsec_day == NINT(0.5_wp * rdt) .OR. kt==nit000) .AND. zflag==1 ) THEN 
    300299        ! 
     
    334333 
    335334      DO itide = 1, nb_harmo 
    336          igrd=1                              ! SSH on tracer grid 
    337          DO ib = 1, ilen0(igrd) 
    338             dta%ssh(ib) = dta%ssh(ib) + zramp*(td%ssh(ib,itide,1)*z_cost(itide) + td%ssh(ib,itide,2)*z_sist(itide)) 
    339          END DO 
    340          igrd=2                              ! U grid 
    341          DO ib = 1, ilen0(igrd) 
    342             dta%u2d(ib) = dta%u2d(ib) + zramp*(td%u  (ib,itide,1)*z_cost(itide) + td%u  (ib,itide,2)*z_sist(itide)) 
    343          END DO 
    344          igrd=3                              ! V grid 
    345          DO ib = 1, ilen0(igrd)  
    346             dta%v2d(ib) = dta%v2d(ib) + zramp*(td%v  (ib,itide,1)*z_cost(itide) + td%v  (ib,itide,2)*z_sist(itide)) 
    347          END DO 
     335         ! SSH on tracer grid 
     336         IF( ASSOCIATED(dta%ssh) ) THEN   ! we use bdy ssh on this mpi subdomain 
     337           DO ib = 1, SIZE(dta%ssh) 
     338               dta%ssh(ib) = dta%ssh(ib) + zramp*(td%ssh(ib,itide,1)*z_cost(itide) + td%ssh(ib,itide,2)*z_sist(itide)) 
     339            END DO 
     340         ENDIF 
     341         ! U grid 
     342         IF( ASSOCIATED(dta%u2d) ) THEN   ! we use bdy u2d on this mpi subdomain 
     343            DO ib = 1, SIZE(dta%u2d) 
     344               dta%u2d(ib) = dta%u2d(ib) + zramp*(td%u  (ib,itide,1)*z_cost(itide) + td%u  (ib,itide,2)*z_sist(itide)) 
     345            END DO 
     346         ENDIF 
     347         ! V grid 
     348         IF( ASSOCIATED(dta%v2d) ) THEN   ! we use bdy v2d on this mpi subdomain 
     349            DO ib = 1, SIZE(dta%v2d)  
     350               dta%v2d(ib) = dta%v2d(ib) + zramp*(td%v  (ib,itide,1)*z_cost(itide) + td%v  (ib,itide,2)*z_sist(itide)) 
     351            END DO 
     352         ENDIF 
    348353      END DO 
    349354      ! 
     
    368373      ! 
    369374      LOGICAL  ::   lk_first_btstp            ! =.TRUE. if time splitting and first barotropic step 
    370       INTEGER  ::   itide, ib_bdy, ib, igrd   ! loop indices 
     375      INTEGER  ::   itide, ib_bdy, ib         ! loop indices 
    371376      INTEGER  ::   time_add                  ! time offset in units of timesteps 
    372       INTEGER, DIMENSION(jpbgrd)   ::   ilen0  
    373       INTEGER, DIMENSION(1:jpbgrd) ::   nblen, nblenrim  ! short cuts 
    374377      REAL(wp) ::   z_arg, z_sarg, zramp, zoff, z_cost, z_sist       
    375378      !!---------------------------------------------------------------------- 
     
    398401         IF( nn_dyn2d_dta(ib_bdy) >= 2 ) THEN 
    399402            ! 
    400             nblen(1:jpbgrd) = idx_bdy(ib_bdy)%nblen(1:jpbgrd) 
    401             nblenrim(1:jpbgrd) = idx_bdy(ib_bdy)%nblenrim(1:jpbgrd) 
    402             ! 
    403             IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN   ;   ilen0(:) = nblen   (:) 
    404             ELSE                                   ;   ilen0(:) = nblenrim(:) 
    405             ENDIF      
    406             ! 
    407403            ! We refresh nodal factors every day below 
    408404            ! This should be done somewhere else 
     
    425421            ! If time splitting, initialize arrays from slow varying open boundary data: 
    426422            IF ( PRESENT(kit) ) THEN            
    427                IF ( dta_bdy(ib_bdy)%lneed_ssh   ) dta_bdy(ib_bdy)%ssh(1:ilen0(1)) = dta_bdy_s(ib_bdy)%ssh(1:ilen0(1)) 
    428                IF ( dta_bdy(ib_bdy)%lneed_dyn2d ) dta_bdy(ib_bdy)%u2d(1:ilen0(2)) = dta_bdy_s(ib_bdy)%u2d(1:ilen0(2)) 
    429                IF ( dta_bdy(ib_bdy)%lneed_dyn2d ) dta_bdy(ib_bdy)%v2d(1:ilen0(3)) = dta_bdy_s(ib_bdy)%v2d(1:ilen0(3)) 
     423               IF ( ASSOCIATED(dta_bdy(ib_bdy)%ssh) ) dta_bdy(ib_bdy)%ssh(:) = dta_bdy_s(ib_bdy)%ssh(:) 
     424               IF ( ASSOCIATED(dta_bdy(ib_bdy)%u2d) ) dta_bdy(ib_bdy)%u2d(:) = dta_bdy_s(ib_bdy)%u2d(:) 
     425               IF ( ASSOCIATED(dta_bdy(ib_bdy)%v2d) ) dta_bdy(ib_bdy)%v2d(:) = dta_bdy_s(ib_bdy)%v2d(:) 
    430426            ENDIF 
    431427            ! 
     
    437433               z_sist = zramp * SIN( z_sarg ) 
    438434               ! 
    439                IF ( dta_bdy(ib_bdy)%lneed_ssh ) THEN 
    440                   igrd=1                              ! SSH on tracer grid 
    441                   DO ib = 1, ilen0(igrd) 
     435               IF ( ASSOCIATED(dta_bdy(ib_bdy)%ssh) ) THEN   ! SSH on tracer grid 
     436                  DO ib = 1, SIZE(dta_bdy(ib_bdy)%ssh) 
    442437                     dta_bdy(ib_bdy)%ssh(ib) = dta_bdy(ib_bdy)%ssh(ib) + & 
    443438                        &                      ( tides(ib_bdy)%ssh(ib,itide,1)*z_cost + & 
     
    446441               ENDIF 
    447442               ! 
    448                IF ( dta_bdy(ib_bdy)%lneed_dyn2d ) THEN 
    449                   igrd=2                              ! U grid 
    450                   DO ib = 1, ilen0(igrd) 
     443               IF ( ASSOCIATED(dta_bdy(ib_bdy)%u2d) ) THEN  ! U grid 
     444                  DO ib = 1, SIZE(dta_bdy(ib_bdy)%u2d) 
    451445                     dta_bdy(ib_bdy)%u2d(ib) = dta_bdy(ib_bdy)%u2d(ib) + & 
    452446                        &                      ( tides(ib_bdy)%u(ib,itide,1)*z_cost + & 
    453447                        &                        tides(ib_bdy)%u(ib,itide,2)*z_sist ) 
    454448                  END DO 
    455                   igrd=3                              ! V grid 
    456                   DO ib = 1, ilen0(igrd)  
     449               ENDIF 
     450               ! 
     451               IF ( ASSOCIATED(dta_bdy(ib_bdy)%v2d) ) THEN   ! V grid 
     452                  DO ib = 1, SIZE(dta_bdy(ib_bdy)%v2d) 
    457453                     dta_bdy(ib_bdy)%v2d(ib) = dta_bdy(ib_bdy)%v2d(ib) + & 
    458454                        &                      ( tides(ib_bdy)%v(ib,itide,1)*z_cost + & 
     
    460456                  END DO 
    461457               ENDIF 
     458               ! 
    462459            END DO              
    463460         END IF 
     
    474471      TYPE(TIDES_DATA), INTENT(inout) ::   td    ! tidal harmonics data 
    475472      ! 
    476       INTEGER ::   itide, igrd, ib       ! dummy loop indices 
    477       INTEGER, DIMENSION(1) ::   ilen0   ! length of boundary data (from OBC arrays) 
     473      INTEGER ::   itide, isz, ib       ! dummy loop indices 
    478474      REAL(wp),ALLOCATABLE, DIMENSION(:) ::   mod_tide, phi_tide 
    479475      !!---------------------------------------------------------------------- 
    480476      ! 
    481       igrd=1    
    482                               ! SSH on tracer grid. 
    483       ilen0(1) =  SIZE(td%ssh0(:,1,1)) 
    484       ! 
    485       ALLOCATE( mod_tide(ilen0(igrd)), phi_tide(ilen0(igrd)) ) 
    486       ! 
    487       DO itide = 1, nb_harmo 
    488          DO ib = 1, ilen0(igrd) 
    489             mod_tide(ib)=SQRT(td%ssh0(ib,itide,1)**2.+td%ssh0(ib,itide,2)**2.) 
    490             phi_tide(ib)=ATAN2(-td%ssh0(ib,itide,2),td%ssh0(ib,itide,1)) 
     477      IF( ASSOCIATED(td%ssh0) ) THEN   ! SSH on tracer grid. 
     478         ! 
     479         isz = SIZE( td%ssh0, dim = 1 ) 
     480         ALLOCATE( mod_tide(isz), phi_tide(isz) ) 
     481         ! 
     482         DO itide = 1, nb_harmo 
     483            DO ib = 1, isz 
     484               mod_tide(ib)=SQRT( td%ssh0(ib,itide,1)*td%ssh0(ib,itide,1) + td%ssh0(ib,itide,2)*td%ssh0(ib,itide,2) ) 
     485               phi_tide(ib)=ATAN2(-td%ssh0(ib,itide,2),td%ssh0(ib,itide,1)) 
     486            END DO 
     487            DO ib = 1, isz 
     488               mod_tide(ib)=mod_tide(ib)*ftide(itide) 
     489               phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
     490            END DO 
     491            DO ib = 1, isz 
     492               td%ssh(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
     493               td%ssh(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
     494            END DO 
    491495         END DO 
    492          DO ib = 1 , ilen0(igrd) 
    493             mod_tide(ib)=mod_tide(ib)*ftide(itide) 
    494             phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
    495          ENDDO 
    496          DO ib = 1 , ilen0(igrd) 
    497             td%ssh(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
    498             td%ssh(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
    499          ENDDO 
    500       END DO 
    501       ! 
    502       DEALLOCATE( mod_tide, phi_tide ) 
     496         ! 
     497         DEALLOCATE( mod_tide, phi_tide ) 
     498         ! 
     499      ENDIF 
    503500      ! 
    504501   END SUBROUTINE tide_init_elevation 
     
    512509      TYPE(TIDES_DATA), INTENT(inout) ::   td    ! tidal harmonics data 
    513510      ! 
    514       INTEGER ::   itide, igrd, ib       ! dummy loop indices 
    515       INTEGER, DIMENSION(3) ::   ilen0   ! length of boundary data (from OBC arrays) 
     511      INTEGER ::   itide, isz, ib        ! dummy loop indices 
    516512      REAL(wp),ALLOCATABLE, DIMENSION(:) ::   mod_tide, phi_tide 
    517513      !!---------------------------------------------------------------------- 
    518514      ! 
    519       ilen0(2) =  SIZE(td%u0(:,1,1)) 
    520       ilen0(3) =  SIZE(td%v0(:,1,1)) 
    521       ! 
    522       igrd=2                                 ! U grid. 
    523       ! 
    524       ALLOCATE( mod_tide(ilen0(igrd)) , phi_tide(ilen0(igrd)) ) 
    525       ! 
    526       DO itide = 1, nb_harmo 
    527          DO ib = 1, ilen0(igrd) 
    528             mod_tide(ib)=SQRT(td%u0(ib,itide,1)**2.+td%u0(ib,itide,2)**2.) 
    529             phi_tide(ib)=ATAN2(-td%u0(ib,itide,2),td%u0(ib,itide,1)) 
     515      IF( ASSOCIATED(td%u0) ) THEN   ! U grid. we use bdy u2d on this mpi subdomain 
     516         ! 
     517         isz = SIZE( td%u0, dim = 1 ) 
     518         ALLOCATE( mod_tide(isz), phi_tide(isz) ) 
     519         ! 
     520         DO itide = 1, nb_harmo 
     521            DO ib = 1, isz 
     522               mod_tide(ib)=SQRT( td%u0(ib,itide,1)*td%u0(ib,itide,1) + td%u0(ib,itide,2)*td%u0(ib,itide,2) ) 
     523               phi_tide(ib)=ATAN2(-td%u0(ib,itide,2),td%u0(ib,itide,1)) 
     524            END DO 
     525            DO ib = 1, isz 
     526               mod_tide(ib)=mod_tide(ib)*ftide(itide) 
     527               phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
     528            END DO 
     529            DO ib = 1, isz 
     530               td%u(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
     531               td%u(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
     532            END DO 
    530533         END DO 
    531          DO ib = 1, ilen0(igrd) 
    532             mod_tide(ib)=mod_tide(ib)*ftide(itide) 
    533             phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
    534          ENDDO 
    535          DO ib = 1, ilen0(igrd) 
    536             td%u(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
    537             td%u(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
    538          ENDDO 
    539       END DO 
    540       ! 
    541       DEALLOCATE( mod_tide , phi_tide ) 
    542       ! 
    543       igrd=3                                 ! V grid. 
    544       ! 
    545       ALLOCATE( mod_tide(ilen0(igrd)) , phi_tide(ilen0(igrd)) ) 
    546  
    547       DO itide = 1, nb_harmo 
    548          DO ib = 1, ilen0(igrd) 
    549             mod_tide(ib)=SQRT(td%v0(ib,itide,1)**2.+td%v0(ib,itide,2)**2.) 
    550             phi_tide(ib)=ATAN2(-td%v0(ib,itide,2),td%v0(ib,itide,1)) 
     534         ! 
     535         DEALLOCATE( mod_tide, phi_tide ) 
     536         ! 
     537      ENDIF 
     538      ! 
     539      IF( ASSOCIATED(td%v0) ) THEN   ! V grid. we use bdy u2d on this mpi subdomain 
     540         ! 
     541         isz = SIZE( td%v0, dim = 1 ) 
     542         ALLOCATE( mod_tide(isz), phi_tide(isz) ) 
     543         ! 
     544         DO itide = 1, nb_harmo 
     545            DO ib = 1, isz 
     546               mod_tide(ib)=SQRT( td%v0(ib,itide,1)*td%v0(ib,itide,1) + td%v0(ib,itide,2)*td%v0(ib,itide,2) ) 
     547               phi_tide(ib)=ATAN2(-td%v0(ib,itide,2),td%v0(ib,itide,1)) 
     548            END DO 
     549            DO ib = 1, isz 
     550               mod_tide(ib)=mod_tide(ib)*ftide(itide) 
     551               phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
     552            END DO 
     553            DO ib = 1, isz 
     554               td%v(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
     555               td%v(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
     556            END DO 
    551557         END DO 
    552          DO ib = 1, ilen0(igrd) 
    553             mod_tide(ib)=mod_tide(ib)*ftide(itide) 
    554             phi_tide(ib)=phi_tide(ib)+v0tide(itide)+utide(itide) 
    555          ENDDO 
    556          DO ib = 1, ilen0(igrd) 
    557             td%v(ib,itide,1)= mod_tide(ib)*COS(phi_tide(ib)) 
    558             td%v(ib,itide,2)=-mod_tide(ib)*SIN(phi_tide(ib)) 
    559          ENDDO 
    560       END DO 
    561       ! 
    562       DEALLOCATE( mod_tide, phi_tide ) 
    563       ! 
    564   END SUBROUTINE tide_init_velocities 
     558         ! 
     559         DEALLOCATE( mod_tide, phi_tide ) 
     560         ! 
     561      ENDIF 
     562      ! 
     563   END SUBROUTINE tide_init_velocities 
    565564 
    566565   !!====================================================================== 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/C1D/step_c1d.F90

    r10068 r12955  
    5454      ! 
    5555      INTEGER ::   jk       ! dummy loop indice 
    56       INTEGER ::   indic    ! error indicator if < 0 
    5756      !! --------------------------------------------------------------------- 
    58  
    59                              indic = 0                ! reset to no error condition 
    6057      IF( kstp == nit000 )   CALL iom_init( "nemo")   ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    6158      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init) 
     
    131128      ! Control and restarts 
    132129      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    133                              CALL stp_ctl( kstp, indic ) 
     130                             CALL stp_ctl( kstp ) 
    134131      IF( kstp == nit000 )   CALL iom_close( numror )      ! close input  ocean restart file 
    135132      IF( lrst_oce       )   CALL rst_write( kstp )        ! write output ocean restart file 
    136133      ! 
    137134#if defined key_iomput 
    138       IF( kstp == nitend .OR. indic < 0 )   CALL xios_context_finalize()   ! needed for XIOS 
     135      IF( kstp == nitend .OR. nstop > 0 )   CALL xios_context_finalize()   ! needed for XIOS 
    139136      ! 
    140137#endif 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DOM/dom_oce.F90

    r12816 r12955  
    233233      Agrif_CFixed = '0'  
    234234   END FUNCTION Agrif_CFixed 
     235 
     236   INTEGER FUNCTION Agrif_Fixed() 
     237      Agrif_Fixed = 0  
     238   END FUNCTION Agrif_Fixed 
    235239#endif 
    236240 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/IOM/in_out_manager.F90

    r11536 r12955  
    159159   INTEGER       ::   no_print = 0          !: optional argument of fld_fill (if present, suppress some control print) 
    160160   INTEGER       ::   nstop = 0             !: error flag (=number of reason for a premature stop run) 
     161!$AGRIF_DO_NOT_TREAT 
     162   INTEGER       ::   ngrdstop = -1         !: grid number having nstop > 1 
     163!$AGRIF_END_DO_NOT_TREAT 
    161164   INTEGER       ::   nwarn = 0             !: warning flag (=number of warning found during the run) 
    162165   CHARACTER(lc) ::   ctmp1, ctmp2, ctmp3   !: temporary characters 1 to 3 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/IOM/iom.F90

    r12598 r12955  
    24602460#else 
    24612461      IF( .FALSE. )   WRITE(numout,*) cdname, pmiss_val   ! useless test to avoid compilation warnings 
     2462      IF( .FALSE. )   pmiss_val = 0._wp                   ! useless assignment to avoid compilation warnings 
    24622463#endif 
    24632464   END SUBROUTINE iom_miss_val 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/LBC/lib_mpp.F90

    r12518 r12955  
    10841084      CHARACTER(len=*), INTENT(in   ), OPTIONAL ::        cd2, cd3, cd4, cd5 
    10851085      CHARACTER(len=*), INTENT(in   ), OPTIONAL ::   cd6, cd7, cd8, cd9, cd10 
     1086      ! 
     1087      INTEGER ::   inum 
    10861088      !!---------------------------------------------------------------------- 
    10871089      ! 
    10881090      nstop = nstop + 1 
    10891091      ! 
    1090       ! force to open ocean.output file if not already opened 
    1091       IF( numout == 6 ) CALL ctl_opn( numout, 'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     1092      IF( numout == 6 ) THEN                          ! force to open ocean.output file if not already opened 
     1093         CALL ctl_opn( numout, 'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     1094      ELSE 
     1095         IF( narea > 1 .AND. cd1 == 'STOP' ) THEN     ! add an error message in ocean.output 
     1096            CALL ctl_opn( inum,'ocean.output', 'APPEND', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     1097            WRITE(inum,*) 
     1098            WRITE(inum,'(a,i4.4)') ' ===>>> : see E R R O R in ocean.output_', narea - 1 
     1099         ENDIF 
     1100      ENDIF 
    10921101      ! 
    10931102                            WRITE(numout,*) 
     
    11171126         WRITE(numout,*)  'huge E-R-R-O-R : immediate stop' 
    11181127         WRITE(numout,*)   
     1128         CALL FLUSH(numout) 
     1129         CALL SLEEP(60)   ! make sure that all output and abort files are written by all cores. 60s should be enough... 
    11191130         CALL mppstop( ld_abort = .true. ) 
    11201131      ENDIF 
     
    12061217         &  OPEN(UNIT=knum,FILE='NUL', FORM=cdform, ACCESS=cdacce, STATUS=cdstat                      , ERR=100, IOSTAT=iost )    
    12071218      IF( iost == 0 ) THEN 
    1208          IF(ldwp) THEN 
     1219         IF(ldwp .AND. kout > 0) THEN 
    12091220            WRITE(kout,*) '     file   : ', TRIM(clfile),' open ok' 
    12101221            WRITE(kout,*) '     unit   = ', knum 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/LBC/mpp_loc_generic.h90

    r10716 r12955  
    3232      REAL(wp)        , INTENT(  out) ::   pmin    ! Global minimum of ptab 
    3333      INDEX_TYPE(:)                                ! index of minimum in global frame 
    34 # if defined key_mpp_mpi 
    3534      ! 
    3635      INTEGER  ::   ierror, ii, idim 
     
    7776      ! 
    7877      IF( ln_timing ) CALL tic_tac(.TRUE., ld_global = .TRUE.) 
     78#if defined key_mpp_mpi 
    7979      CALL MPI_ALLREDUCE( zain, zaout, 1, MPI_2DOUBLE_PRECISION, MPI_OPERATION ,MPI_COMM_OCE, ierror) 
     80#else 
     81      zaout(:,:) = zain(:,:) 
     82#endif 
    8083      IF( ln_timing ) CALL tic_tac(.FALSE., ld_global = .TRUE.) 
    8184      ! 
     
    9295      kindex(1) = index0 
    9396      kindex(:) = kindex(:) + 1   ! start indices at 1 
    94 #else 
    95       kindex = 0 ; pmin = 0. 
    96       WRITE(*,*) 'ROUTINE_LOC: You should not have seen this print! error?' 
    97 #endif 
    9897 
    9998   END SUBROUTINE ROUTINE_LOC 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbcblk.F90

    r12894 r12955  
    7878   REAL(wp), PARAMETER ::   R_vap = 461.495_wp    !: Specific gas constant for water vapor          [J/K/kg] 
    7979   REAL(wp), PARAMETER ::   reps0 = R_dry/R_vap   !: ratio of gas constant for dry air and water vapor => ~ 0.622 
    80    REAL(wp), PARAMETER ::   rctv0 = R_vap/R_dry   !: for virtual temperature (== (1-eps)/eps) => ~ 0.608 
     80   REAL(wp), PARAMETER ::   rctv0 = R_vap/R_dry - 1._wp !: for virtual temperature (== (1-eps)/eps) => ~ 0.608 
    8181 
    8282   INTEGER , PARAMETER ::   jpfld   =11           ! maximum number of files to read 
     
    720720      REAL(wp) ::   zwndi_f , zwndj_f, zwnorm_f   ! relative wind module and components at F-point 
    721721      REAL(wp) ::   zwndi_t , zwndj_t             ! relative wind components at T-point 
     722      REAL(wp) ::   zztmp1  , zztmp2              ! temporary values 
    722723      REAL(wp), DIMENSION(jpi,jpj) ::   zrhoa     ! transfer coefficient for momentum      (tau) 
    723724      !!--------------------------------------------------------------------- 
     
    758759      zrhoa (:,:) =  rho_air(sf(jp_tair)%fnow(:,:,1), sf(jp_humi)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1)) 
    759760 
    760       !!gm brutal.... 
    761       utau_ice  (:,:) = 0._wp 
    762       vtau_ice  (:,:) = 0._wp 
    763       !!gm end 
    764  
    765761      ! ------------------------------------------------------------ ! 
    766762      !    Wind stress relative to the moving ice ( U10m - U_ice )   ! 
    767763      ! ------------------------------------------------------------ ! 
    768       ! C-grid ice dynamics :   U & V-points (same as ocean) 
    769       DO jj = 2, jpjm1 
     764      zztmp1 = rn_vfac * 0.5_wp 
     765      DO jj = 2, jpj    ! at T point 
     766         DO ji = 2, jpi 
     767            zztmp2 = zrhoa(ji,jj) * Cd_atm(ji,jj) * wndm_ice(ji,jj) 
     768            utau_ice(ji,jj) = zztmp2 * ( sf(jp_wndi)%fnow(ji,jj,1) - zztmp1 * ( u_ice(ji-1,jj  ) + u_ice(ji,jj) ) ) 
     769            vtau_ice(ji,jj) = zztmp2 * ( sf(jp_wndj)%fnow(ji,jj,1) - zztmp1 * ( v_ice(ji  ,jj-1) + v_ice(ji,jj) ) ) 
     770         END DO 
     771      END DO 
     772      ! 
     773      DO jj = 2, jpjm1  ! U & V-points (same as ocean). 
    770774         DO ji = fs_2, fs_jpim1   ! vect. opt. 
    771             utau_ice(ji,jj) = 0.5 * zrhoa(ji,jj) * Cd_atm(ji,jj) * ( wndm_ice(ji+1,jj  ) + wndm_ice(ji,jj) )            & 
    772                &          * ( 0.5 * (sf(jp_wndi)%fnow(ji+1,jj,1) + sf(jp_wndi)%fnow(ji,jj,1) ) - rn_vfac * u_ice(ji,jj) ) 
    773             vtau_ice(ji,jj) = 0.5 * zrhoa(ji,jj) * Cd_atm(ji,jj) * ( wndm_ice(ji,jj+1  ) + wndm_ice(ji,jj) )            & 
    774                &          * ( 0.5 * (sf(jp_wndj)%fnow(ji,jj+1,1) + sf(jp_wndj)%fnow(ji,jj,1) ) - rn_vfac * v_ice(ji,jj) ) 
     775            ! take care of the land-sea mask to avoid "pollution" of coastal stress. p[uv]taui used in frazil and  rheology  
     776            zztmp1 = 0.5_wp * ( 2. - umask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji+1,jj  ,1) ) 
     777            zztmp2 = 0.5_wp * ( 2. - vmask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji  ,jj+1,1) ) 
     778            utau_ice(ji,jj) = zztmp1 * ( utau_ice(ji,jj) + utau_ice(ji+1,jj  ) ) 
     779            vtau_ice(ji,jj) = zztmp2 * ( vtau_ice(ji,jj) + vtau_ice(ji  ,jj+1) ) 
    775780         END DO 
    776781      END DO 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbccpl.F90

    r12948 r12955  
    15031503      INTEGER ::   ji, jj   ! dummy loop indices 
    15041504      INTEGER ::   itx      ! index of taux over ice 
     1505      REAL(wp)                     ::   zztmp1, zztmp2 
    15051506      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty  
    15061507      !!---------------------------------------------------------------------- 
     
    15661567            p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! (U,V) ==> (U,V) 
    15671568            p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1) 
    1568          CASE( 'F' ) 
    1569             DO jj = 2, jpjm1                                   ! F ==> (U,V) 
    1570                DO ji = fs_2, fs_jpim1   ! vector opt. 
    1571                   p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj-1,1) ) 
    1572                   p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji,jj,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1) ) 
    1573                END DO 
    1574             END DO 
    15751569         CASE( 'T' ) 
    15761570            DO jj = 2, jpjm1                                   ! T ==> (U,V) 
    15771571               DO ji = fs_2, fs_jpim1   ! vector opt. 
    1578                   p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) ) 
    1579                   p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) ) 
     1572                  ! take care of the land-sea mask to avoid "pollution" of coastal stress. p[uv]taui used in frazil and  rheology  
     1573                  zztmp1 = 0.5_wp * ( 2. - umask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji+1,jj  ,1) ) 
     1574                  zztmp2 = 0.5_wp * ( 2. - vmask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji  ,jj+1,1) ) 
     1575                  p_taui(ji,jj) = zztmp1 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) ) 
     1576                  p_tauj(ji,jj) = zztmp2 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) ) 
    15801577               END DO 
    15811578            END DO 
    1582          CASE( 'I' ) 
    1583             DO jj = 2, jpjm1                                   ! I ==> (U,V) 
    1584                DO ji = 2, jpim1   ! NO vector opt. 
    1585                   p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1) ) 
    1586                   p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji+1,jj+1,1) + frcv(jpr_ity1)%z3(ji  ,jj+1,1) ) 
    1587                END DO 
    1588             END DO 
     1579            CALL lbc_lnk_multi( 'sbccpl', p_taui, 'U',  -1., p_tauj, 'V',  -1. ) 
    15891580         END SELECT 
    1590          IF( srcv(jpr_itx1)%clgrid /= 'U' ) THEN  
    1591             CALL lbc_lnk_multi( 'sbccpl', p_taui, 'U',  -1., p_tauj, 'V',  -1. ) 
    1592          ENDIF 
    15931581          
    15941582      ENDIF 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/nemogcm.F90

    r12640 r12955  
    179179      END DO 
    180180      ! 
    181       IF( .NOT. Agrif_Root() ) THEN 
    182          CALL Agrif_ParentGrid_To_ChildGrid() 
    183          IF( ln_diaobs )   CALL dia_obs_wri 
    184          IF( ln_timing )   CALL timing_finalize 
    185          CALL Agrif_ChildGrid_To_ParentGrid() 
    186       ENDIF 
    187       ! 
    188181# else 
    189182      ! 
     
    230223      IF( nstop /= 0 .AND. lwp ) THEN        ! error print 
    231224         WRITE(ctmp1,*) '   ==>>>   nemo_gcm: a total of ', nstop, ' errors have been found' 
    232          CALL ctl_stop( ctmp1 ) 
     225         IF( ngrdstop > 0 ) THEN 
     226            WRITE(ctmp9,'(i2)') ngrdstop 
     227            WRITE(ctmp2,*) '      ==>>>   Error detected in Agrif grid '//TRIM(ctmp9) 
     228            WRITE(ctmp3,*) '      ==>>>   look for error messages in '//TRIM(ctmp9)//'_ocean_output* files' 
     229            CALL ctl_stop( ctmp1, ctmp2, ctmp3 ) 
     230         ELSE 
     231            CALL ctl_stop( ctmp1 ) 
     232         ENDIF 
    233233      ENDIF 
    234234      ! 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/step.F90

    r12651 r12955  
    7676      !!---------------------------------------------------------------------- 
    7777      INTEGER ::   ji, jj, jk   ! dummy loop indice 
    78       INTEGER ::   indic        ! error indicator if < 0 
    7978!!gm kcall can be removed, I guess 
    8079      INTEGER ::   kcall        ! optional integer argument (dom_vvl_sf_nxt) 
    8180      !! --------------------------------------------------------------------- 
    8281#if defined key_agrif 
    83       IF( nstop > 0 ) return   ! avoid to go further if an error was detected during previous time step  
     82      IF( nstop > 0 ) RETURN   ! avoid to go further if an error was detected during previous time step (child grid) 
    8483      kstp = nit000 + Agrif_Nb_Step() 
    8584      IF( lk_agrif_debug ) THEN 
     
    9897      ! update I/O and calendar  
    9998      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    100                              indic = 0                ! reset to no error condition 
    101                               
    10299      IF( kstp == nit000 ) THEN                       ! initialize IOM context (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    103100                             CALL iom_init(      cxios_context          )  ! for model grid (including passible AGRIF zoom) 
     
    288285      ! Control 
    289286      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    290                          CALL stp_ctl      ( kstp, indic ) 
     287                         CALL stp_ctl      ( kstp ) 
    291288                          
    292289#if defined key_agrif 
     
    294291      ! AGRIF update 
    295292      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
    296       IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) CALL Agrif_update_all( ) ! Update all components 
     293      IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) THEN 
     294                         CALL Agrif_update_all( )                  ! Update all components 
     295      ENDIF 
    297296#endif 
    298297 
     
    312311      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    313312!!gm why lk_oasis and not lk_cpl ???? 
    314       IF( lk_oasis   )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     313      IF( lk_oasis .AND. nstop == 0 )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    315314      ! 
    316315#if defined key_iomput 
     
    318317      ! Finalize contextes if end of simulation or error detected 
    319318      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<                          
    320       IF( kstp == nitend .OR. indic < 0 ) THEN  
    321                       CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
     319      IF( kstp == nitend .OR. nstop > 0 ) THEN  
     320                      CALL iom_context_finalize(       cxios_context         ) ! needed for XIOS+AGRIF 
    322321         IF( lrxios ) CALL iom_context_finalize(      crxios_context         ) 
    323322         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
     
    328327      ! 
    329328   END SUBROUTINE stp 
    330     
     329   ! 
    331330   !!====================================================================== 
    332331END MODULE step 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/stpctl.F90

    r11407 r12955  
    3434 
    3535   INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 
    36    LOGICAL  ::   lsomeoce 
    3736   !!---------------------------------------------------------------------- 
    3837   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    4241CONTAINS 
    4342 
    44    SUBROUTINE stp_ctl( kt, kindic ) 
     43   SUBROUTINE stp_ctl( kt ) 
    4544      !!---------------------------------------------------------------------- 
    4645      !!                    ***  ROUTINE stp_ctl  *** 
     
    5049      !! ** Method  : - Save the time step in numstp 
    5150      !!              - Print it each 50 time steps 
    52       !!              - Stop the run IF problem encountered by setting indic=-3 
     51      !!              - Stop the run IF problem encountered by setting nstop > 0 
    5352      !!                Problems checked: |ssh| maximum larger than 10 m 
    5453      !!                                  |U|   maximum larger than 10 m/s  
     
    5756      !! ** Actions :   "time.step" file = last ocean time-step 
    5857      !!                "run.stat"  file = run statistics 
    59       !!                nstop indicator sheared among all local domain (lk_mpp=T) 
     58      !!                 nstop indicator sheared among all local domain 
    6059      !!---------------------------------------------------------------------- 
    6160      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
    62       INTEGER, INTENT(inout) ::   kindic   ! error indicator 
    6361      !! 
    6462      INTEGER                ::   ji, jj, jk          ! dummy loop indices 
    65       INTEGER, DIMENSION(2)  ::   ih                  ! min/max loc indices 
    66       INTEGER, DIMENSION(3)  ::   iu, is1, is2        ! min/max loc indices 
     63      INTEGER,  DIMENSION(3) ::   ih, iu, is1, is2    ! min/max loc indices 
     64      INTEGER,  DIMENSION(9) ::   iareasum, iareamin, iareamax 
    6765      REAL(wp)               ::   zzz                 ! local real  
    68       REAL(wp), DIMENSION(9) ::   zmax 
     66      REAL(wp), DIMENSION(9) ::   zmax, zmaxlocal 
    6967      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns 
    7068      CHARACTER(len=20) :: clname 
    7169      !!---------------------------------------------------------------------- 
    72       ! 
    73       ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    74       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
    75       ll_wrtruns = ll_colruns .AND. lwm 
    76       IF( kt == nit000 .AND. lwp ) THEN 
    77          WRITE(numout,*) 
    78          WRITE(numout,*) 'stp_ctl : time-stepping control' 
    79          WRITE(numout,*) '~~~~~~~' 
     70      IF( nstop > 0 .AND. ngrdstop > -1 )   RETURN   !   stpctl was already called by a child grid 
     71      ! 
     72      ll_wrtstp  = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
     73      ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1  
     74      ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 
     75      ! 
     76      IF( kt == nit000 ) THEN 
     77         ! 
     78         IF( lwp ) THEN 
     79            WRITE(numout,*) 
     80            WRITE(numout,*) 'stp_ctl : time-stepping control' 
     81            WRITE(numout,*) '~~~~~~~' 
     82         ENDIF 
    8083         !                                ! open time.step file 
    8184         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8285         !                                ! open run.stat file(s) at start whatever 
    8386         !                                ! the value of sn_cfctl%ptimincr 
    84          IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
     87         IF( ll_wrtruns ) THEN 
    8588            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8689            clname = 'run.stat.nc' 
     
    99102            ENDIF 
    100103            istatus = NF90_ENDDEF(idrun) 
    101             zmax(8:9) = 0._wp    ! initialise to zero in case ln_zad_Aimp option is not in use 
    102          ENDIF 
    103       ENDIF 
    104       IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
     104         ENDIF 
     105      ENDIF 
    105106      ! 
    106107      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
     
    118119      zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   ! minus salinity max 
    119120      zmax(4) = MAXVAL(  tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   !       salinity max 
    120       zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   ! minus temperature max 
    121       zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   !       temperature max 
     121      IF( ll_colruns ) THEN     ! following variables are used only in the netcdf file 
     122         zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   ! minus temperature max 
     123         zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   !       temperature max 
     124         IF( ln_zad_Aimp ) THEN 
     125            zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
     126            zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) ! partitioning coeff. max 
     127         ELSE 
     128            zmax(8:9) = 0._wp 
     129         ENDIF 
     130      ELSE 
     131         zmax(5:9) = 0._wp 
     132      ENDIF 
    122133      zmax(7) = REAL( nstop , wp )                                            ! stop indicator 
    123       IF( ln_zad_Aimp ) THEN 
    124          zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
    125          zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) ! partitioning coeff. max 
    126       ENDIF 
    127134      ! 
    128135      IF( ll_colruns ) THEN 
     136         zmaxlocal(:) = zmax(:) 
    129137         CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
    130138         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains 
     
    143151            istatus = NF90_PUT_VAR( idrun,  idc1, (/ zmax(9)/), (/kt/), (/1/) ) 
    144152         ENDIF 
    145          IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 
    146          IF( kt == nitend         ) istatus = NF90_CLOSE(idrun) 
     153         IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 
    147154      END IF 
    148155      !                                   !==  error handling  ==! 
    149       IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
    150          &  zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
     156      IF(   zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
    151157         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
    152158         &  zmax(3) >=   0._wp .OR.   &                    ! negative or zero sea surface salinity 
    153159         &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 ) 
    154160         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
    155          &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
    156          IF( lk_mpp .AND. ln_ctl ) THEN 
    157             CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih  ) 
     161         &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR.  &   ! NaN encounter in the tests 
     162         &  ABS(   zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN    ! Infinity encounter in the tests 
     163         IF( ll_colruns ) THEN 
     164            ! first: close the netcdf file, so we can read it 
     165            IF( lwm .AND. kt /= nitend )   istatus = NF90_CLOSE(idrun) 
     166            CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih(1:2)  )   ;   ih(3) = 0 
    158167            CALL mpp_maxloc( 'stpctl', ABS(un)          , umask (:,:,:), zzz, iu  ) 
    159168            CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 ) 
    160169            CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 ) 
     170            ! find which subdomain has the max. 
     171            iareamin(:) = jpnij+1   ;   iareamax(:) = 0   ;   iareasum(:) = 0 
     172            DO ji = 1, 9 
     173               IF( zmaxlocal(ji) == zmax(ji) ) THEN 
     174                  iareamin(ji) = narea   ;   iareamax(ji) = narea   ;   iareasum(ji) = 1 
     175               ENDIF 
     176            END DO 
     177            CALL mpp_min( "stpctl", iareamin )         ! min over the global domain 
     178            CALL mpp_max( "stpctl", iareamax )         ! max over the global domain 
     179            CALL mpp_sum( "stpctl", iareasum )         ! sum over the global domain 
    161180         ELSE 
    162             ih(:)  = MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /) 
     181            ih(1:2)= MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /)   ;   ih(3) = 0 
    163182            iu(:)  = MAXLOC( ABS( un  (:,:,:) )                              ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    164183            is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    165184            is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    166          ENDIF 
    167           
     185            iareamin(:) = narea   ;   iareamax(:) = narea   ;   iareasum(:) = 1         ! this is local information 
     186         ENDIF 
     187         ! 
    168188         WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests' 
    169          WRITE(ctmp2,9100) kt,   zmax(1), ih(1) , ih(2) 
    170          WRITE(ctmp3,9200) kt,   zmax(2), iu(1) , iu(2) , iu(3) 
    171          WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 
    172          WRITE(ctmp5,9400) kt,   zmax(4), is2(1), is2(2), is2(3) 
    173          WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort.nc file' 
    174           
    175          CALL dia_wri_state( 'output.abort' )     ! create an output.abort file 
    176           
    177          IF( .NOT. ln_ctl ) THEN 
    178             WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 
    179             CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 
     189         CALL wrt_line(ctmp2, kt, ' |ssh| max ',   zmax(1), ih , iareasum(1), iareamin(1), iareamax(1) )  
     190         CALL wrt_line(ctmp3, kt, ' |U|   max ',   zmax(2), iu , iareasum(2), iareamin(2), iareamax(2) )  
     191         CALL wrt_line(ctmp4, kt, ' Sal   min ', - zmax(3), is1, iareasum(3), iareamin(3), iareamax(3) )  
     192         CALL wrt_line(ctmp5, kt, ' Sal   max ',   zmax(4), is2, iareasum(4), iareamin(4), iareamax(4) )  
     193         IF( Agrif_Root() ) THEN 
     194            WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort* files' 
    180195         ELSE 
    181             CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 
    182          ENDIF 
    183  
    184          kindic = -3 
    185          ! 
    186       ENDIF 
    187       ! 
    188 9100  FORMAT (' kt=',i8,'   |ssh| max: ',1pg11.4,', at  i j  : ',2i5) 
    189 9200  FORMAT (' kt=',i8,'   |U|   max: ',1pg11.4,', at  i j k: ',3i5) 
    190 9300  FORMAT (' kt=',i8,'   S     min: ',1pg11.4,', at  i j k: ',3i5) 
    191 9400  FORMAT (' kt=',i8,'   S     max: ',1pg11.4,', at  i j k: ',3i5) 
     196            WRITE(ctmp6,*) '      ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 
     197         ENDIF 
     198         ! 
     199         CALL dia_wri_state( 'output.abort' )    ! create an output.abort file 
     200         ! 
     201         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
     202            IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     203         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
     204            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     205         ENDIF 
     206         ! 
     207         IF( nstop == 0 )   nstop = 1  
     208         ngrdstop = Agrif_Fixed() 
     209         ! 
     210      ENDIF 
     211      ! 
    1922129500  FORMAT(' it :', i8, '    |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 
    193213      ! 
    194214   END SUBROUTINE stp_ctl 
     215 
     216 
     217   SUBROUTINE wrt_line( cdline, kt, cdprefix, pval, kloc, ksum, kmin, kmax ) 
     218      !!---------------------------------------------------------------------- 
     219      !!                     ***  ROUTINE wrt_line  *** 
     220      !! 
     221      !! ** Purpose :   write information line 
     222      !! 
     223      !!---------------------------------------------------------------------- 
     224      CHARACTER(len=*),      INTENT(  out) ::   cdline 
     225      CHARACTER(len=*),      INTENT(in   ) ::   cdprefix 
     226      REAL(wp),              INTENT(in   ) ::   pval 
     227      INTEGER, DIMENSION(3), INTENT(in   ) ::   kloc 
     228      INTEGER,               INTENT(in   ) ::   kt, ksum, kmin, kmax 
     229      ! 
     230      CHARACTER(len=80) ::   clsuff 
     231      CHARACTER(len=9 ) ::   clkt, clsum, clmin, clmax 
     232      CHARACTER(len=9 ) ::   cli, clj, clk 
     233      CHARACTER(len=1 ) ::   clfmt 
     234      CHARACTER(len=4 ) ::   cl4   ! needed to be able to compile with Agrif, I don't know why 
     235      INTEGER           ::   ifmtk 
     236      !!---------------------------------------------------------------------- 
     237      WRITE(clkt , '(i9)') kt 
     238       
     239      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij  ,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9) 
     240      !!! WRITE(clsum, '(i'//clfmt//')') ksum                   ! this is creating a compilation error with AGRIF 
     241      cl4 = '(i'//clfmt//')'   ;   WRITE(clsum, cl4) ksum 
     242      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij-1,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9) 
     243      cl4 = '(i'//clfmt//')'   ;   WRITE(clmin, cl4) kmin-1 
     244                                   WRITE(clmax, cl4) kmax-1 
     245      ! 
     246      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1      ! how many digits to we need to write jpiglo? (we decide max = 9) 
     247      cl4 = '(i'//clfmt//')'   ;   WRITE(cli, cl4) kloc(1)      ! this is ok with AGRIF 
     248      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpjglo,wp))) + 1      ! how many digits to we need to write jpjglo? (we decide max = 9) 
     249      cl4 = '(i'//clfmt//')'   ;   WRITE(clj, cl4) kloc(2)      ! this is ok with AGRIF 
     250      ! 
     251      IF( ksum == 1 ) THEN   ;   WRITE(clsuff,9100) TRIM(clmin) 
     252      ELSE                   ;   WRITE(clsuff,9200) TRIM(clsum), TRIM(clmin), TRIM(clmax) 
     253      ENDIF 
     254      IF(kloc(3) == 0) THEN 
     255         ifmtk = INT(LOG10(REAL(jpk,wp))) + 1                   ! how many digits to we need to write jpk? (we decide max = 9) 
     256         clk = REPEAT(' ', ifmtk)                               ! create the equivalent in blank string 
     257         WRITE(cdline,9300) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), clk(1:ifmtk), TRIM(clsuff) 
     258      ELSE 
     259         WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1      ! how many digits to we need to write jpk? (we decide max = 9) 
     260         !!! WRITE(clk, '(i'//clfmt//')') kloc(3)               ! this is creating a compilation error with AGRIF 
     261         cl4 = '(i'//clfmt//')'   ;   WRITE(clk, cl4) kloc(3)   ! this is ok with AGRIF 
     262         WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj),    TRIM(clk), TRIM(clsuff) 
     263      ENDIF 
     264      ! 
     2659100  FORMAT('MPI rank ', a) 
     2669200  FORMAT('found in ', a, ' MPI tasks, spread out among ranks ', a, ' to ', a) 
     2679300  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j   ', a, ' ', a, ' ', a, ' ', a) 
     2689400  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j k ', a, ' ', a, ' ', a, ' ', a) 
     269      ! 
     270   END SUBROUTINE wrt_line 
     271 
    195272 
    196273   !!====================================================================== 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/SAS/stpctl.F90

    r10603 r12955  
    3232 
    3333   INTEGER  ::   idrun, idtime, idssh, idu, ids, istatus 
    34    LOGICAL  ::   lsomeoce 
    3534   !!---------------------------------------------------------------------- 
    3635   !! NEMO/SAS 4.0 , NEMO Consortium (2018) 
     
    6261      !!---------------------------------------------------------------------- 
    6362      ! 
    64       ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    65       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
    66       ll_wrtruns = ll_colruns .AND. lwm 
    67       IF( kt == nit000 .AND. lwp ) THEN 
    68          WRITE(numout,*) 
    69          WRITE(numout,*) 'stp_ctl : time-stepping control' 
    70          WRITE(numout,*) '~~~~~~~' 
     63      ll_wrtstp  = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
     64      ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1  
     65      ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 
     66      ! 
     67      IF( kt == nit000 ) THEN 
     68         ! 
     69         IF( lwp ) THEN 
     70            WRITE(numout,*) 
     71            WRITE(numout,*) 'stp_ctl : time-stepping control' 
     72            WRITE(numout,*) '~~~~~~~' 
     73         ENDIF 
    7174         !                                ! open time.step file 
    7275         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    7376         !                                ! open run.stat file(s) at start whatever 
    7477         !                                ! the value of sn_cfctl%ptimincr 
    75          IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
     78         IF( ll_wrtruns ) THEN 
    7679            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    7780            clname = 'run.stat.nc' 
     
    8588         ENDIF 
    8689      ENDIF 
    87       IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
    8890      ! 
    8991      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
     
    9294      ENDIF 
    9395      !                                   !==  test of extrema  ==! 
    94       IF( ll_colruns ) THEN 
     96      IF( ll_colruns .OR. jpnij == 1 ) THEN 
    9597         zmax(1) = MAXVAL(      vt_i (:,:) )                                           ! max ice thickness 
    9698         zmax(2) = MAXVAL( ABS( u_ice(:,:) ) )                                         ! max ice velocity (zonal only) 
    9799         zmax(3) = MAXVAL(     -tm_i (:,:)+273.15_wp , mask = ssmask(:,:) == 1._wp )   ! min ice temperature 
    98          CALL mpp_max( "stpctl", zmax )                                   ! max over the global domain 
     100         IF( ll_colruns )   CALL mpp_max( "stpctl", zmax )                             ! max over the global domain 
    99101      END IF 
    100102      !                                            !==  run statistics  ==!   ("run.stat" file) 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/CANAL/MY_SRC/stpctl.F90

    r10572 r12955  
    3434 
    3535   INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 
    36    LOGICAL  ::   lsomeoce 
    3736   !!---------------------------------------------------------------------- 
    3837   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    4241CONTAINS 
    4342 
    44    SUBROUTINE stp_ctl( kt, kindic ) 
     43   SUBROUTINE stp_ctl( kt ) 
    4544      !!---------------------------------------------------------------------- 
    4645      !!                    ***  ROUTINE stp_ctl  *** 
     
    5049      !! ** Method  : - Save the time step in numstp 
    5150      !!              - Print it each 50 time steps 
    52       !!              - Stop the run IF problem encountered by setting indic=-3 
     51      !!              - Stop the run IF problem encountered by setting nstop > 0 
    5352      !!                Problems checked: |ssh| maximum larger than 10 m 
    5453      !!                                  |U|   maximum larger than 10 m/s  
     
    5756      !! ** Actions :   "time.step" file = last ocean time-step 
    5857      !!                "run.stat"  file = run statistics 
    59       !!                nstop indicator sheared among all local domain (lk_mpp=T) 
     58      !!                 nstop indicator sheared among all local domain 
    6059      !!---------------------------------------------------------------------- 
    6160      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
    62       INTEGER, INTENT(inout) ::   kindic   ! error indicator 
    6361      !! 
    6462      INTEGER                ::   ji, jj, jk          ! dummy loop indices 
    65       INTEGER, DIMENSION(2)  ::   ih                  ! min/max loc indices 
    66       INTEGER, DIMENSION(3)  ::   iu, is1, is2        ! min/max loc indices 
     63      INTEGER,  DIMENSION(3) ::   ih, iu, is1, is2    ! min/max loc indices 
     64      INTEGER,  DIMENSION(9) ::   iareasum, iareamin, iareamax 
    6765      REAL(wp)               ::   zzz                 ! local real  
    68       REAL(wp), DIMENSION(9) ::   zmax 
     66      REAL(wp), DIMENSION(9) ::   zmax, zmaxlocal 
    6967      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns 
    7068      CHARACTER(len=20) :: clname 
    7169      !!---------------------------------------------------------------------- 
    72       ! 
    73       ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    74       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
    75       ll_wrtruns = ll_colruns .AND. lwm 
    76       IF( kt == nit000 .AND. lwp ) THEN 
    77          WRITE(numout,*) 
    78          WRITE(numout,*) 'stp_ctl : time-stepping control' 
    79          WRITE(numout,*) '~~~~~~~' 
     70      IF( nstop > 0 .AND. ngrdstop > -1 )   RETURN   !   stpctl was already called by a child grid 
     71      ! 
     72      ll_wrtstp  = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
     73      ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1  
     74      ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 
     75      ! 
     76      IF( kt == nit000 ) THEN 
     77         ! 
     78         IF( lwp ) THEN 
     79            WRITE(numout,*) 
     80            WRITE(numout,*) 'stp_ctl : time-stepping control' 
     81            WRITE(numout,*) '~~~~~~~' 
     82         ENDIF 
    8083         !                                ! open time.step file 
    8184         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8285         !                                ! open run.stat file(s) at start whatever 
    8386         !                                ! the value of sn_cfctl%ptimincr 
    84          IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
     87         IF( ll_wrtruns ) THEN 
    8588            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8689            clname = 'run.stat.nc' 
     
    9699            IF( ln_zad_Aimp ) THEN 
    97100               istatus = NF90_DEF_VAR( idrun,   'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1  ) 
    98                istatus = NF90_DEF_VAR( idrun,       'Cu_max', NF90_DOUBLE, (/ idtime /), idc1  ) 
     101               istatus = NF90_DEF_VAR( idrun,       'Cf_max', NF90_DOUBLE, (/ idtime /), idc1  ) 
    99102            ENDIF 
    100103            istatus = NF90_ENDDEF(idrun) 
    101             zmax(8:9) = 0._wp    ! initialise to zero in case ln_zad_Aimp option is not in use 
    102          ENDIF 
    103       ENDIF 
    104       IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
     104         ENDIF 
     105      ENDIF 
    105106      ! 
    106107      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
     
    118119      zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   ! minus salinity max 
    119120      zmax(4) = MAXVAL(  tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   !       salinity max 
    120       zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   ! minus temperature max 
    121       zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   !       temperature max 
     121      IF( ll_colruns ) THEN     ! following variables are used only in the netcdf file 
     122         zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   ! minus temperature max 
     123         zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   !       temperature max 
     124         IF( ln_zad_Aimp ) THEN 
     125            zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
     126            zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) ! partitioning coeff. max 
     127         ELSE 
     128            zmax(8:9) = 0._wp 
     129         ENDIF 
     130      ELSE 
     131         zmax(5:9) = 0._wp 
     132      ENDIF 
    122133      zmax(7) = REAL( nstop , wp )                                            ! stop indicator 
    123       IF( ln_zad_Aimp ) THEN 
    124          zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
    125          zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) !       cell Courant no. max 
    126       ENDIF 
    127134      ! 
    128135      IF( ll_colruns ) THEN 
     136         zmaxlocal(:) = zmax(:) 
    129137         CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
    130138         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains 
     
    143151            istatus = NF90_PUT_VAR( idrun,  idc1, (/ zmax(9)/), (/kt/), (/1/) ) 
    144152         ENDIF 
    145          IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 
    146          IF( kt == nitend         ) istatus = NF90_CLOSE(idrun) 
     153         IF( kt == nitend ) istatus = NF90_CLOSE(idrun) 
    147154      END IF 
    148155      !                                   !==  error handling  ==! 
    149       IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
    150          &  zmax(1) >   50._wp .OR.   &                    ! too large sea surface height ( > 50 m ) 
    151          &  zmax(2) >   20._wp .OR.   &                    ! too large velocity ( > 20 m/s) 
     156      IF(   zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
     157         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
    152158!!$         &  zmax(3) >=   0._wp .OR.   &                    ! negative or zero sea surface salinity 
    153159!!$         &  zmax(4) >= 100._wp .OR.   &                    ! too large sea surface salinity ( > 100 ) 
    154160!!$         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
    155          &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
    156          IF( lk_mpp .AND. ln_ctl ) THEN 
    157             CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih  ) 
     161         &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) .OR.  &   ! NaN encounter in the tests 
     162         &  ABS(   zmax(1) + zmax(2) + zmax(3) ) > HUGE(1._wp) ) THEN    ! Infinity encounter in the tests 
     163         IF( ll_colruns ) THEN 
     164            ! first: close the netcdf file, so we can read it 
     165            IF( lwm .AND. kt /= nitend )   istatus = NF90_CLOSE(idrun) 
     166            CALL mpp_maxloc( 'stpctl', ABS(sshn)        , ssmask(:,:)  , zzz, ih(1:2)  )   ;   ih(3) = 0 
    158167            CALL mpp_maxloc( 'stpctl', ABS(un)          , umask (:,:,:), zzz, iu  ) 
    159168            CALL mpp_minloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is1 ) 
    160169            CALL mpp_maxloc( 'stpctl', tsn(:,:,:,jp_sal), tmask (:,:,:), zzz, is2 ) 
     170            ! find which subdomain has the max. 
     171            iareamin(:) = jpnij+1   ;   iareamax(:) = 0   ;   iareasum(:) = 0 
     172            DO ji = 1, 9 
     173               IF( zmaxlocal(ji) == zmax(ji) ) THEN 
     174                  iareamin(ji) = narea   ;   iareamax(ji) = narea   ;   iareasum(ji) = 1 
     175               ENDIF 
     176            END DO 
     177            CALL mpp_min( "stpctl", iareamin )         ! min over the global domain 
     178            CALL mpp_max( "stpctl", iareamax )         ! max over the global domain 
     179            CALL mpp_sum( "stpctl", iareasum )         ! sum over the global domain 
    161180         ELSE 
    162             ih(:)  = MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /) 
     181            ih(1:2)= MAXLOC( ABS( sshn(:,:)   )                              ) + (/ nimpp - 1, njmpp - 1    /)   ;   ih(3) = 0 
    163182            iu(:)  = MAXLOC( ABS( un  (:,:,:) )                              ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    164183            is1(:) = MINLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    165184            is2(:) = MAXLOC( tsn(:,:,:,jp_sal), mask = tmask(:,:,:) == 1._wp ) + (/ nimpp - 1, njmpp - 1, 0 /) 
    166          ENDIF 
    167           
    168          WRITE(ctmp1,*) ' stp_ctl: |ssh| > 50 m  or  |U| > 20 m/s  or  NaN encounter in the tests' 
    169          WRITE(ctmp2,9100) kt,   zmax(1), ih(1) , ih(2) 
    170          WRITE(ctmp3,9200) kt,   zmax(2), iu(1) , iu(2) , iu(3) 
    171          WRITE(ctmp4,9300) kt, - zmax(3), is1(1), is1(2), is1(3) 
    172          WRITE(ctmp5,9400) kt,   zmax(4), is2(1), is2(2), is2(3) 
    173          WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort.nc file' 
    174           
    175          CALL dia_wri_state( 'output.abort' )     ! create an output.abort file 
    176           
    177          IF( .NOT. ln_ctl ) THEN 
    178             WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 
    179             CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 
     185            iareamin(:) = narea   ;   iareamax(:) = narea   ;   iareasum(:) = 1         ! this is local information 
     186         ENDIF 
     187         ! 
     188         WRITE(ctmp1,*) ' stp_ctl: |ssh| > 20 m  or  |U| > 10 m/s  or  S <= 0  or  S >= 100  or  NaN encounter in the tests' 
     189         CALL wrt_line(ctmp2, kt, ' |ssh| max ',   zmax(1), ih , iareasum(1), iareamin(1), iareamax(1) )  
     190         CALL wrt_line(ctmp3, kt, ' |U|   max ',   zmax(2), iu , iareasum(2), iareamin(2), iareamax(2) )  
     191         CALL wrt_line(ctmp4, kt, ' Sal   min ', - zmax(3), is1, iareasum(3), iareamin(3), iareamax(3) )  
     192         CALL wrt_line(ctmp5, kt, ' Sal   max ',   zmax(4), is2, iareasum(4), iareamin(4), iareamax(4) )  
     193         IF( Agrif_Root() ) THEN 
     194            WRITE(ctmp6,*) '      ===> output of last computed fields in output.abort* files' 
    180195         ELSE 
    181             CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6, ' ' ) 
    182          ENDIF 
    183  
    184          kindic = -3 
    185          ! 
    186       ENDIF 
    187       ! 
    188 9100  FORMAT (' kt=',i8,'   |ssh| max: ',1pg11.4,', at  i j  : ',2i5) 
    189 9200  FORMAT (' kt=',i8,'   |U|   max: ',1pg11.4,', at  i j k: ',3i5) 
    190 9300  FORMAT (' kt=',i8,'   S     min: ',1pg11.4,', at  i j k: ',3i5) 
    191 9400  FORMAT (' kt=',i8,'   S     max: ',1pg11.4,', at  i j k: ',3i5) 
     196            WRITE(ctmp6,*) '      ===> output of last computed fields in '//TRIM(Agrif_CFixed())//'_output.abort* files' 
     197         ENDIF 
     198         ! 
     199         CALL dia_wri_state( 'output.abort' )    ! create an output.abort file 
     200         ! 
     201         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
     202            IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     203         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
     204            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     205         ENDIF 
     206         ! 
     207         IF( nstop == 0 )   nstop = 1  
     208         ngrdstop = Agrif_Fixed() 
     209         ! 
     210      ENDIF 
     211      ! 
    1922129500  FORMAT(' it :', i8, '    |ssh|_max: ', D23.16, ' |U|_max: ', D23.16,' S_min: ', D23.16,' S_max: ', D23.16) 
    193213      ! 
    194214   END SUBROUTINE stp_ctl 
     215 
     216 
     217   SUBROUTINE wrt_line( cdline, kt, cdprefix, pval, kloc, ksum, kmin, kmax ) 
     218      !!---------------------------------------------------------------------- 
     219      !!                     ***  ROUTINE wrt_line  *** 
     220      !! 
     221      !! ** Purpose :   write information line 
     222      !! 
     223      !!---------------------------------------------------------------------- 
     224      CHARACTER(len=*),      INTENT(  out) ::   cdline 
     225      CHARACTER(len=*),      INTENT(in   ) ::   cdprefix 
     226      REAL(wp),              INTENT(in   ) ::   pval 
     227      INTEGER, DIMENSION(3), INTENT(in   ) ::   kloc 
     228      INTEGER,               INTENT(in   ) ::   kt, ksum, kmin, kmax 
     229      ! 
     230      CHARACTER(len=80) ::   clsuff 
     231      CHARACTER(len=9 ) ::   clkt, clsum, clmin, clmax 
     232      CHARACTER(len=9 ) ::   cli, clj, clk 
     233      CHARACTER(len=1 ) ::   clfmt 
     234      CHARACTER(len=4 ) ::   cl4   ! needed to be able to compile with Agrif, I don't know why 
     235      INTEGER           ::   ifmtk 
     236      !!---------------------------------------------------------------------- 
     237      WRITE(clkt , '(i9)') kt 
     238       
     239      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij  ,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9) 
     240      !!! WRITE(clsum, '(i'//clfmt//')') ksum                   ! this is creating a compilation error with AGRIF 
     241      cl4 = '(i'//clfmt//')'   ;   WRITE(clsum, cl4) ksum 
     242      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij-1,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9) 
     243      cl4 = '(i'//clfmt//')'   ;   WRITE(clmin, cl4) kmin-1 
     244                                   WRITE(clmax, cl4) kmax-1 
     245      ! 
     246      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1      ! how many digits to we need to write jpiglo? (we decide max = 9) 
     247      cl4 = '(i'//clfmt//')'   ;   WRITE(cli, cl4) kloc(1)      ! this is ok with AGRIF 
     248      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpjglo,wp))) + 1      ! how many digits to we need to write jpjglo? (we decide max = 9) 
     249      cl4 = '(i'//clfmt//')'   ;   WRITE(clj, cl4) kloc(2)      ! this is ok with AGRIF 
     250      ! 
     251      IF( ksum == 1 ) THEN   ;   WRITE(clsuff,9100) TRIM(clmin) 
     252      ELSE                   ;   WRITE(clsuff,9200) TRIM(clsum), TRIM(clmin), TRIM(clmax) 
     253      ENDIF 
     254      IF(kloc(3) == 0) THEN 
     255         ifmtk = INT(LOG10(REAL(jpk,wp))) + 1                   ! how many digits to we need to write jpk? (we decide max = 9) 
     256         clk = REPEAT(' ', ifmtk)                               ! create the equivalent in blank string 
     257         WRITE(cdline,9300) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj), clk(1:ifmtk), TRIM(clsuff) 
     258      ELSE 
     259         WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1      ! how many digits to we need to write jpk? (we decide max = 9) 
     260         !!! WRITE(clk, '(i'//clfmt//')') kloc(3)               ! this is creating a compilation error with AGRIF 
     261         cl4 = '(i'//clfmt//')'   ;   WRITE(clk, cl4) kloc(3)   ! this is ok with AGRIF 
     262         WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj),    TRIM(clk), TRIM(clsuff) 
     263      ENDIF 
     264      ! 
     2659100  FORMAT('MPI rank ', a) 
     2669200  FORMAT('found in ', a, ' MPI tasks, spread out among ranks ', a, ' to ', a) 
     2679300  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j   ', a, ' ', a, ' ', a, ' ', a) 
     2689400  FORMAT('kt ', a, ' ', a, ' ', 1pg11.4, ' at i j k ', a, ' ', a, ' ', a, ' ', a) 
     269      ! 
     270   END SUBROUTINE wrt_line 
     271 
    195272 
    196273   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.