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 12377 for NEMO/trunk/src/OCE/LBC – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/OCE/LBC/lbclnk.F90

    r11536 r12377  
    6262   INTEGER, PUBLIC, PARAMETER ::   jpfillmpi     = 5 
    6363 
     64   !! * Substitutions 
     65#  include "do_loop_substitute.h90" 
    6466   !!---------------------------------------------------------------------- 
    6567   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
  • NEMO/trunk/src/OCE/LBC/lib_mpp.F90

    r11536 r12377  
    3232   !!   ctl_opn       : Open file and check if required file is available. 
    3333   !!   ctl_nam       : Prints informations when an error occurs while reading a namelist 
     34   !!   load_nml      : Read, condense and buffer namelist file into character array for use as an internal file 
    3435   !!---------------------------------------------------------------------- 
    3536   !!---------------------------------------------------------------------- 
     
    5051   !!   mpp_ini_north : initialisation of north fold 
    5152   !!   mpp_lbc_north_icb : alternative to mpp_nfd for extra outer halo with icebergs 
     53   !!   mpp_bcast_nml : broadcast/receive namelist character buffer from reading process to all others 
    5254   !!---------------------------------------------------------------------- 
    5355   USE dom_oce        ! ocean space and time domain 
     
    5759   PRIVATE 
    5860   ! 
    59    PUBLIC   ctl_stop, ctl_warn, ctl_opn, ctl_nam 
     61   PUBLIC   ctl_stop, ctl_warn, ctl_opn, ctl_nam, load_nml 
    6062   PUBLIC   mpp_start, mppstop, mppsync, mpp_comm_free 
    6163   PUBLIC   mpp_ini_north 
     
    6668   PUBLIC   mppsend, mpprecv                          ! needed by TAM and ICB routines 
    6769   PUBLIC   mpp_report 
     70   PUBLIC   mpp_bcast_nml 
    6871   PUBLIC   tic_tac 
    6972#if ! defined key_mpp_mpi 
     
    139142   INTEGER, PUBLIC                               ::   ncom_stp = 0                 !: copy of time step # istp 
    140143   INTEGER, PUBLIC                               ::   ncom_fsbc = 1                !: copy of sbc time step # nn_fsbc 
    141    INTEGER, PUBLIC                               ::   ncom_dttrc = 1               !: copy of top time step # nn_dttrc 
    142144   INTEGER, PUBLIC                               ::   ncom_freq                    !: frequency of comm diagnostic 
    143145   INTEGER, PUBLIC , DIMENSION(:,:), ALLOCATABLE ::   ncomm_sequence               !: size of communicated arrays (halos) 
     
    170172   LOGICAL, PUBLIC ::   l_north_nogather = .FALSE.  !: internal control of northfold comms 
    171173    
     174   !! * Substitutions 
     175#  include "do_loop_substitute.h90" 
    172176   !!---------------------------------------------------------------------- 
    173177   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    499503#endif 
    500504   END SUBROUTINE mpp_delay_rcv 
     505 
     506   SUBROUTINE mpp_bcast_nml( cdnambuff , kleng ) 
     507      CHARACTER(LEN=:)    , ALLOCATABLE, INTENT(INOUT) :: cdnambuff 
     508      INTEGER                          , INTENT(INOUT) :: kleng 
     509      !!---------------------------------------------------------------------- 
     510      !!                  ***  routine mpp_bcast_nml  *** 
     511      !! 
     512      !! ** Purpose :   broadcast namelist character buffer 
     513      !! 
     514      !!---------------------------------------------------------------------- 
     515      !! 
     516      INTEGER ::   iflag 
     517      !!---------------------------------------------------------------------- 
     518      ! 
     519#if defined key_mpp_mpi 
     520      call MPI_BCAST(kleng, 1, MPI_INT, 0, mpi_comm_oce, iflag) 
     521      call MPI_BARRIER(mpi_comm_oce, iflag) 
     522!$AGRIF_DO_NOT_TREAT 
     523      IF ( .NOT. ALLOCATED(cdnambuff) ) ALLOCATE( CHARACTER(LEN=kleng) :: cdnambuff ) 
     524!$AGRIF_END_DO_NOT_TREAT 
     525      call MPI_BCAST(cdnambuff, kleng, MPI_CHARACTER, 0, mpi_comm_oce, iflag) 
     526      call MPI_BARRIER(mpi_comm_oce, iflag) 
     527#endif 
     528      ! 
     529   END SUBROUTINE mpp_bcast_nml 
    501530 
    502531    
     
    921950      ! 
    922951      ! find the smallest common frequency: default = frequency product, if multiple, choose the larger of the 2 frequency 
    923       IF( ncom_dttrc /= 1 )   CALL ctl_stop( 'STOP', 'mpp_report, ncom_dttrc /= 1 not coded...' )  
    924952      ncom_freq = ncom_fsbc 
    925953      ! 
     
    10681096 
    10691097   !!---------------------------------------------------------------------- 
    1070    !!   ctl_stop, ctl_warn, get_unit, ctl_opn, ctl_nam   routines 
     1098   !!   ctl_stop, ctl_warn, get_unit, ctl_opn, ctl_nam, load_nml   routines 
    10711099   !!---------------------------------------------------------------------- 
    10721100 
     
    12041232         &  OPEN(UNIT=knum,FILE='NUL', FORM=cdform, ACCESS=cdacce, STATUS=cdstat                      , ERR=100, IOSTAT=iost )    
    12051233      IF( iost == 0 ) THEN 
    1206          IF(ldwp) THEN 
     1234         IF(ldwp .AND. kout > 0) THEN 
    12071235            WRITE(kout,*) '     file   : ', TRIM(clfile),' open ok' 
    12081236            WRITE(kout,*) '     unit   = ', knum 
     
    12791307   END FUNCTION get_unit 
    12801308 
     1309   SUBROUTINE load_nml( cdnambuff , cdnamfile, kout, ldwp) 
     1310      CHARACTER(LEN=:)    , ALLOCATABLE, INTENT(INOUT) :: cdnambuff 
     1311      CHARACTER(LEN=*), INTENT(IN )                :: cdnamfile 
     1312      CHARACTER(LEN=256)                           :: chline 
     1313      CHARACTER(LEN=1)                             :: csp 
     1314      INTEGER, INTENT(IN)                          :: kout 
     1315      LOGICAL, INTENT(IN)                          :: ldwp  !: .true. only for the root broadcaster 
     1316      INTEGER                                      :: itot, iun, iltc, inl, ios, itotsav 
     1317      ! 
     1318      !csp = NEW_LINE('A') 
     1319      ! a new line character is the best seperator but some systems (e.g.Cray) 
     1320      ! seem to terminate namelist reads from internal files early if they  
     1321      ! encounter new-lines. Use a single space for safety. 
     1322      csp = ' ' 
     1323      ! 
     1324      ! Check if the namelist buffer has already been allocated. Return if it has. 
     1325      ! 
     1326      IF ( ALLOCATED( cdnambuff ) ) RETURN 
     1327      IF( ldwp ) THEN 
     1328         ! 
     1329         ! Open namelist file 
     1330         ! 
     1331         CALL ctl_opn( iun, cdnamfile, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, kout, ldwp ) 
     1332         ! 
     1333         ! First pass: count characters excluding comments and trimable white space 
     1334         ! 
     1335         itot=0 
     1336     10  READ(iun,'(A256)',END=20,ERR=20) chline 
     1337         iltc = LEN_TRIM(chline) 
     1338         IF ( iltc.GT.0 ) THEN 
     1339          inl = INDEX(chline, '!')  
     1340          IF( inl.eq.0 ) THEN 
     1341           itot = itot + iltc + 1                                ! +1 for the newline character 
     1342          ELSEIF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl-1) ).GT.0 ) THEN 
     1343           itot = itot + inl                                  !  includes +1 for the newline character 
     1344          ENDIF 
     1345         ENDIF 
     1346         GOTO 10 
     1347     20  CONTINUE 
     1348         ! 
     1349         ! Allocate text cdnambuff for condensed namelist 
     1350         ! 
     1351!$AGRIF_DO_NOT_TREAT 
     1352         ALLOCATE( CHARACTER(LEN=itot) :: cdnambuff ) 
     1353!$AGRIF_END_DO_NOT_TREAT 
     1354         itotsav = itot 
     1355         ! 
     1356         ! Second pass: read and transfer pruned characters into cdnambuff 
     1357         ! 
     1358         REWIND(iun) 
     1359         itot=1 
     1360     30  READ(iun,'(A256)',END=40,ERR=40) chline 
     1361         iltc = LEN_TRIM(chline) 
     1362         IF ( iltc.GT.0 ) THEN 
     1363          inl = INDEX(chline, '!') 
     1364          IF( inl.eq.0 ) THEN 
     1365           inl = iltc 
     1366          ELSE 
     1367           inl = inl - 1 
     1368          ENDIF 
     1369          IF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl) ).GT.0 ) THEN 
     1370             cdnambuff(itot:itot+inl-1) = chline(1:inl) 
     1371             WRITE( cdnambuff(itot+inl:itot+inl), '(a)' ) csp 
     1372             itot = itot + inl + 1 
     1373          ENDIF 
     1374         ENDIF 
     1375         GOTO 30 
     1376     40  CONTINUE 
     1377         itot = itot - 1 
     1378         IF( itotsav .NE. itot ) WRITE(*,*) 'WARNING in load_nml. Allocated ',itotsav,' for read buffer; but used ',itot 
     1379         ! 
     1380         ! Close namelist file 
     1381         ! 
     1382         CLOSE(iun) 
     1383         !write(*,'(32A)') cdnambuff 
     1384      ENDIF 
     1385#if defined key_mpp_mpi 
     1386      CALL mpp_bcast_nml( cdnambuff, itot ) 
     1387#endif 
     1388  END SUBROUTINE load_nml 
     1389 
     1390 
    12811391   !!---------------------------------------------------------------------- 
    12821392END MODULE lib_mpp 
  • NEMO/trunk/src/OCE/LBC/mppini.F90

    r11640 r12377  
    171171      !!---------------------------------------------------------------------- 
    172172      ! 
    173       llwrtlay = lwp .OR. ln_ctl .OR. sn_cfctl%l_layout 
     173      llwrtlay = lwm .OR. sn_cfctl%l_layout 
    174174      ! 
    175175      !  0. read namelists parameters 
    176176      ! ----------------------------------- 
    177177      ! 
    178       REWIND( numnam_ref )              ! Namelist nammpp in reference namelist 
    179178      READ  ( numnam_ref, nammpp, IOSTAT = ios, ERR = 901 ) 
    180179901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nammpp in reference namelist' ) 
    181       REWIND( numnam_cfg )              ! Namelist nammpp in confguration namelist 
    182180      READ  ( numnam_cfg, nammpp, IOSTAT = ios, ERR = 902 ) 
    183181902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nammpp in configuration namelist' )    
     
    197195 
    198196      ! do we need to take into account bdy_msk? 
    199       REWIND( numnam_ref )              ! Namelist nambdy in reference namelist : BDY 
    200197      READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903) 
    201198903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in reference namelist (mppini)' ) 
    202       REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist : BDY 
    203199      READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 904 ) 
    204200904   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambdy in configuration namelist (mppini)' ) 
Note: See TracChangeset for help on using the changeset viewer.