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 11648 for NEMO/branches/2019 – NEMO

Changeset 11648 for NEMO/branches/2019


Ignore:
Timestamp:
2019-10-03T17:57:40+02:00 (5 years ago)
Author:
acc
Message:

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Introduce broadcast of namelist character buffer from single reader to all others. This completes the second stage but there is still an issue with AGRIF that may scupper this whole concept

Location:
NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icestp.F90

    r11624 r11648  
    233233      ! 
    234234      !                                ! Load the reference and configuration namelist files and open namelist output file 
    235       CALL load_nml( numnam_ice_ref, 'namelist_ice_ref',    numout, lwp ) 
    236       CALL load_nml( numnam_ice_cfg, 'namelist_ice_cfg',    numout, lwp ) 
     235      CALL load_nml( numnam_ice_ref, 'namelist_ice_ref',    numout, lwm ) 
     236      CALL load_nml( numnam_ice_cfg, 'namelist_ice_cfg',    numout, lwm ) 
    237237      IF(lwm) CALL ctl_opn( numoni , 'output.namelist.ice', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, 1 ) 
    238238      ! 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/LBC/lib_mpp.F90

    r11624 r11648  
    5151   !!   mpp_ini_north : initialisation of north fold 
    5252   !!   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 
    5354   !!---------------------------------------------------------------------- 
    5455   USE dom_oce        ! ocean space and time domain 
     
    6768   PUBLIC   mppsend, mpprecv                          ! needed by TAM and ICB routines 
    6869   PUBLIC   mpp_report 
     70   PUBLIC   mpp_bcast_nml 
    6971   PUBLIC   tic_tac 
    7072#if ! defined key_mpp_mpi 
     
    500502#endif 
    501503   END SUBROUTINE mpp_delay_rcv 
     504 
     505   SUBROUTINE mpp_bcast_nml( cdnambuff , kleng ) 
     506      CHARACTER(LEN=:)    , ALLOCATABLE, INTENT(INOUT) :: cdnambuff 
     507      INTEGER                          , INTENT(INOUT) :: kleng 
     508      !!---------------------------------------------------------------------- 
     509      !!                  ***  routine mpp_bcast_nml  *** 
     510      !! 
     511      !! ** Purpose :   broadcast namelist character buffer 
     512      !! 
     513      !!---------------------------------------------------------------------- 
     514      !! 
     515      INTEGER ::   iflag 
     516      !!---------------------------------------------------------------------- 
     517      ! 
     518#if defined key_mpp_mpi 
     519      call MPI_BCAST(kleng, 1, MPI_INT, 0, mpi_comm_oce, iflag) 
     520      call MPI_BARRIER(mpi_comm_oce, iflag) 
     521      IF ( .NOT. ALLOCATED(cdnambuff) ) ALLOCATE( CHARACTER(LEN=kleng) :: cdnambuff ) 
     522      call MPI_BCAST(cdnambuff, kleng, MPI_CHARACTER, 0, mpi_comm_oce, iflag) 
     523      call MPI_BARRIER(mpi_comm_oce, iflag) 
     524#endif 
     525      ! 
     526   END SUBROUTINE mpp_bcast_nml 
    502527 
    503528    
     
    12851310      CHARACTER(LEN=256)                           :: chline 
    12861311      INTEGER, INTENT(IN)                          :: kout 
    1287       LOGICAL, INTENT(IN)                          :: ldwp 
     1312      LOGICAL, INTENT(IN)                          :: ldwp  !: .true. only for the root broadcaster 
    12881313      INTEGER                                      :: itot, iun, iltc, inl, ios 
    12891314      ! 
     
    12911316      ! 
    12921317      IF ( ALLOCATED( cdnambuff ) ) RETURN 
    1293       ! 
    1294       ! Open namelist file 
    1295       ! 
    1296       CALL ctl_opn( iun, cdnamfile, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, kout, ldwp ) 
    1297       ! 
    1298       ! First pass: count characters excluding comments and trimable white space 
    1299       ! 
    1300       itot=0 
    1301   10  READ(iun,'(A256)',END=20,ERR=20) chline 
    1302       iltc = LEN_TRIM(chline) 
    1303       IF ( iltc.GT.0 ) THEN 
    1304        inl = INDEX(chline, '!')  
    1305        IF( inl.eq.0 ) THEN 
    1306         itot = itot + iltc + 1                                ! +1 for the newline character 
    1307        ELSEIF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl-1) ).GT.0 ) THEN 
    1308         itot = itot + inl                                  !  includes +1 for the newline character 
    1309        ENDIF 
    1310       ENDIF 
    1311       GOTO 10 
    1312   20  CONTINUE 
    1313       ! 
    1314       ! Allocate text cdnambuff for condensed namelist 
    1315       ! 
    1316       ALLOCATE( CHARACTER(LEN=itot) :: cdnambuff ) 
    1317       WRITE(*,*) 'ALLOCATED ', itot 
    1318       ! 
    1319       ! Second pass: read and transfer pruned characters into cdnambuff 
    1320       ! 
    1321       REWIND(iun) 
    1322       itot=1 
    1323   30  READ(iun,'(A256)',END=40,ERR=40) chline 
    1324       iltc = LEN_TRIM(chline) 
    1325       IF ( iltc.GT.0 ) THEN 
    1326        inl = INDEX(chline, '!') 
    1327        IF( inl.eq.0 ) THEN 
    1328         inl = iltc 
    1329        ELSE 
    1330         inl = inl - 1 
    1331        ENDIF 
    1332        IF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl) ).GT.0 ) THEN 
    1333           cdnambuff(itot:itot+inl-1) = chline(1:inl) 
    1334           WRITE( cdnambuff(itot+inl:itot+inl), '(a)' ) NEW_LINE('A') 
    1335           itot = itot + inl + 1 
    1336        ENDIF 
    1337       ENDIF 
    1338       GOTO 30 
    1339   40  CONTINUE 
    1340       WRITE(*,*) 'ASSIGNED ',itot - 1 
    1341       ! 
    1342       ! Close namelist file 
    1343       ! 
    1344       CLOSE(iun) 
    1345       !write(*,'(32A)') cdnambuff 
     1318      IF( ldwp ) THEN 
     1319         ! 
     1320         ! Open namelist file 
     1321         ! 
     1322         CALL ctl_opn( iun, cdnamfile, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, kout, ldwp ) 
     1323         ! 
     1324         ! First pass: count characters excluding comments and trimable white space 
     1325         ! 
     1326         itot=0 
     1327     10  READ(iun,'(A256)',END=20,ERR=20) chline 
     1328         iltc = LEN_TRIM(chline) 
     1329         IF ( iltc.GT.0 ) THEN 
     1330          inl = INDEX(chline, '!')  
     1331          IF( inl.eq.0 ) THEN 
     1332           itot = itot + iltc + 1                                ! +1 for the newline character 
     1333          ELSEIF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl-1) ).GT.0 ) THEN 
     1334           itot = itot + inl                                  !  includes +1 for the newline character 
     1335          ENDIF 
     1336         ENDIF 
     1337         GOTO 10 
     1338     20  CONTINUE 
     1339         ! 
     1340         ! Allocate text cdnambuff for condensed namelist 
     1341         ! 
     1342         ALLOCATE( CHARACTER(LEN=itot) :: cdnambuff ) 
     1343         WRITE(*,*) 'ALLOCATED ', itot 
     1344         ! 
     1345         ! Second pass: read and transfer pruned characters into cdnambuff 
     1346         ! 
     1347         REWIND(iun) 
     1348         itot=1 
     1349     30  READ(iun,'(A256)',END=40,ERR=40) chline 
     1350         iltc = LEN_TRIM(chline) 
     1351         IF ( iltc.GT.0 ) THEN 
     1352          inl = INDEX(chline, '!') 
     1353          IF( inl.eq.0 ) THEN 
     1354           inl = iltc 
     1355          ELSE 
     1356           inl = inl - 1 
     1357          ENDIF 
     1358          IF( inl.GT.0 .AND. LEN_TRIM( chline(1:inl) ).GT.0 ) THEN 
     1359             cdnambuff(itot:itot+inl-1) = chline(1:inl) 
     1360             WRITE( cdnambuff(itot+inl:itot+inl), '(a)' ) NEW_LINE('A') 
     1361             itot = itot + inl + 1 
     1362          ENDIF 
     1363         ENDIF 
     1364         GOTO 30 
     1365     40  CONTINUE 
     1366         itot = itot - 1 
     1367         WRITE(*,*) 'ASSIGNED ',itot 
     1368         ! 
     1369         ! Close namelist file 
     1370         ! 
     1371         CLOSE(iun) 
     1372         !write(*,'(32A)') cdnambuff 
     1373      ENDIF 
     1374#if defined key_mpp_mpi 
     1375      CALL mpp_bcast_nml( cdnambuff, itot ) 
     1376#endif 
    13461377  END SUBROUTINE load_nml 
    13471378 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/nemogcm.F90

    r11624 r11648  
    307307      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    308308      ! open reference and configuration namelist files 
    309                   CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, .FALSE. ) 
    310                   CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, .FALSE. ) 
     309                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     310                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    311311      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    312312      ! open /dev/null file to be able to supress output write easily 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OFF/nemogcm.F90

    r11624 r11648  
    192192      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    193193      ! open reference and configuration namelist files 
    194                   CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, .FALSE. ) 
    195                   CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, .FALSE. ) 
     194                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     195                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    196196      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    197197      ! open /dev/null file to be able to supress output write easily 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/SAO/nemogcm.F90

    r11624 r11648  
    135135      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    136136      ! open reference and configuration namelist files 
    137                   CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, .FALSE. ) 
    138                   CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, .FALSE. ) 
     137                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     138                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    139139      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    140140      ! open /dev/null file to be able to supress output write easily 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/SAS/nemogcm.F90

    r11624 r11648  
    232232         IF( lwm )   CALL ctl_opn(     numout,               'sas.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    233233         ! open reference and configuration namelist files 
    234                      CALL load_nml( numnam_ref,        'namelist_sas_ref',                                           -1, .FALSE. ) 
    235                      CALL load_nml( numnam_cfg,        'namelist_sas_cfg',                                           -1, .FALSE. ) 
     234                     CALL load_nml( numnam_ref,        'namelist_sas_ref',                                           -1, lwm ) 
     235                     CALL load_nml( numnam_cfg,        'namelist_sas_cfg',                                           -1, lwm ) 
    236236         IF( lwm )   CALL ctl_opn(      numond, 'output.namelist_sas.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    237237      ELSE 
    238238         IF( lwm )   CALL ctl_opn(      numout,            'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    239239         ! open reference and configuration namelist files 
    240                      CALL load_nml( numnam_ref,            'namelist_ref',                                           -1, .FALSE. ) 
    241                      CALL load_nml( numnam_cfg,            'namelist_cfg',                                           -1, .FALSE. ) 
     240                     CALL load_nml( numnam_ref,            'namelist_ref',                                           -1, lwm ) 
     241                     CALL load_nml( numnam_cfg,            'namelist_cfg',                                           -1, lwm ) 
    242242         IF( lwm )   CALL ctl_opn(      numond,     'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    243243      ENDIF 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/PISCES/SED/sedini.F90

    r11624 r11648  
    452452      IF(lwp) WRITE(numsed,*) ' sed_init_nam : read SEDIMENT namelist' 
    453453      IF(lwp) WRITE(numsed,*) ' ~~~~~~~~~~~~~~' 
    454       CALL load_nml( numnamsed_ref, TRIM( clname )//'_ref', numout, .FALSE. ) 
    455       CALL load_nml( numnamsed_cfg, TRIM( clname )//'_cfg', numout, .FALSE. ) 
     454      CALL load_nml( numnamsed_ref, TRIM( clname )//'_ref', numout, lwm ) 
     455      CALL load_nml( numnamsed_cfg, TRIM( clname )//'_cfg', numout, lwm ) 
    456456 
    457457      nitsed000 = nittrc000 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/PISCES/trcnam_pisces.F90

    r11624 r11648  
    5151      IF(lwp) WRITE(numout,*) 'trc_nam_pisces : read PISCES namelist' 
    5252      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~' 
    53       CALL load_nml( numnatp_ref, TRIM( clname )//'_ref', numout, .FALSE. ) 
    54       CALL load_nml( numnatp_cfg, TRIM( clname )//'_cfg', numout, .FALSE. ) 
     53      CALL load_nml( numnatp_ref, TRIM( clname )//'_ref', numout, lwm ) 
     54      CALL load_nml( numnatp_cfg, TRIM( clname )//'_cfg', numout, lwm ) 
    5555      IF(lwm) CALL ctl_opn( numonp     , 'output.namelist.pis' , 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    5656      ! 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/trcnam.F90

    r11624 r11648  
    108108      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    109109      ! 
    110       CALL load_nml( numnat_ref, 'namelist_top_ref' , numout, .FALSE. ) 
    111       CALL load_nml( numnat_cfg, 'namelist_top_cfg' , numout, .FALSE. ) 
     110      CALL load_nml( numnat_ref, 'namelist_top_ref' , numout, lwm ) 
     111      CALL load_nml( numnat_cfg, 'namelist_top_cfg' , numout, lwm ) 
    112112      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 ) 
    113113      ! 
     
    224224      IF( ll_cfc .OR. ln_c14 ) THEN 
    225225        !                             ! Open namelist files 
    226         CALL load_nml( numtrc_ref, 'namelist_trc_ref' , numout, .FALSE. ) 
    227         CALL load_nml( numtrc_cfg, 'namelist_trc_cfg' , numout, .FALSE. ) 
     226        CALL load_nml( numtrc_ref, 'namelist_trc_ref' , numout, lwm ) 
     227        CALL load_nml( numtrc_cfg, 'namelist_trc_cfg' , numout, lwm ) 
    228228        IF(lwm) CALL ctl_opn( numonr, 'output.namelist.trc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    229229        ! 
Note: See TracChangeset for help on using the changeset viewer.