Skip to content

Commit

Permalink
Merge pull request #114 from ecmwf-ifs/samhatfield/remove_ncombflen
Browse files Browse the repository at this point in the history
Remove NCOMBFLEN parameter
  • Loading branch information
samhatfield authored Jul 15, 2024
2 parents c8523be + ec50339 commit f2754fd
Show file tree
Hide file tree
Showing 4 changed files with 8 additions and 8 deletions.
3 changes: 1 addition & 2 deletions src/programs/ectrans-benchmark.F90
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,6 @@ program transform_test

integer(kind=jpim) :: nmax_resol = 37 ! Max number of resolutions
integer(kind=jpim) :: npromatr = 0 ! nproma for trans lib
integer(kind=jpim) :: ncombflen = 1800000 ! Size of comm buffer

integer(kind=jpim) :: nproc ! Number of procs
integer(kind=jpim) :: nthread
Expand Down Expand Up @@ -379,7 +378,7 @@ program transform_test
call gstats(1, 0)
call setup_trans0(kout=nout, kerr=nerr, kprintlev=merge(2, 0, verbosity == 1), &
& kmax_resol=nmax_resol, kpromatr=npromatr, kprgpns=nprgpns, kprgpew=nprgpew, &
& kprtrw=nprtrw, kcombflen=ncombflen, ldsync_trans=lsync_trans, &
& kprtrw=nprtrw, ldsync_trans=lsync_trans, &
& ldeq_regions=leq_regions, prad=zra, ldalloperm=.true., ldmpoff=.not.luse_mpi)
call gstats(1, 1)

Expand Down
10 changes: 6 additions & 4 deletions src/trans/external/setup_trans0.F90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ SUBROUTINE SETUP_TRANS0(KOUT,KERR,KPRINTLEV,KMAX_RESOL,KPROMATR,&
! KPRGPNS - splitting level in N-S direction in grid-point space [1]
! KPRGPEW - splitting level in E-W direction in grid-point space [1]
! KPRTRW - splitting level in wave direction in spectral space [1]
! KCOMBFLEN - Size of communication buffer [1800000 (*8bytes) ]
! KCOMBFLEN - Size of communication buffer [1800000 (*8bytes) ] (deprecated)
! LDMPOFF - switch off message passing [false]
! LDSYNC_TRANS - switch to activate barriers in trmtol trltom [false]
! KTRANS_SYNC_LEVEL - use of synchronization/blocking [0]
Expand Down Expand Up @@ -74,7 +74,7 @@ SUBROUTINE SETUP_TRANS0(KOUT,KERR,KPRINTLEV,KMAX_RESOL,KPROMATR,&

USE TPM_GEN ,ONLY : NERR, NOUT, LMPOFF, LSYNC_TRANS, NTRANS_SYNC_LEVEL, MSETUP0, &
& NMAX_RESOL, NPRINTLEV, NPROMATR, LALLOPERM, NSTACK_MEMORY_TR
USE TPM_DISTR ,ONLY : LEQ_REGIONS, NCOMBFLEN, NPRGPEW,NPRGPNS, NPRTRW
USE TPM_DISTR ,ONLY : LEQ_REGIONS, NPRGPEW, NPRGPNS, NPRTRW
USE TPM_CONSTANTS ,ONLY : RA

USE SUMP_TRANS0_MOD ,ONLY : SUMP_TRANS0
Expand Down Expand Up @@ -121,7 +121,6 @@ SUBROUTINE SETUP_TRANS0(KOUT,KERR,KPRINTLEV,KMAX_RESOL,KPROMATR,&
N_REGIONS_NS=1
N_REGIONS_EW=1
NPROMATR = 0
NCOMBFLEN = 1800000
LMPOFF = .FALSE.
LSYNC_TRANS=.FALSE.
NTRANS_SYNC_LEVEL=0
Expand Down Expand Up @@ -171,7 +170,10 @@ SUBROUTINE SETUP_TRANS0(KOUT,KERR,KPRINTLEV,KMAX_RESOL,KPROMATR,&
NPRTRW = KPRTRW
ENDIF
IF(PRESENT(KCOMBFLEN)) THEN
NCOMBFLEN = KCOMBFLEN
WRITE(NOUT,'(A)')
WRITE(NOUT,'(A)') '*** WARNING ***'
WRITE(NOUT,'(A)') 'KCOMBFLEN argument passed to SETUP_TRANS0 is deprecated'
WRITE(NOUT,'(A)')
ENDIF
IF(PRESENT(LDMPOFF)) THEN
LMPOFF = LDMPOFF
Expand Down
2 changes: 1 addition & 1 deletion src/trans/include/ectrans/setup_trans0.h
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ SUBROUTINE SETUP_TRANS0(KOUT,KERR,KPRINTLEV,KMAX_RESOL,KPROMATR,&
! KPRGPNS - splitting level in N-S direction in grid-point space [1]
! KPRGPEW - splitting level in E-W direction in grid-point space [1]
! KPRTRW - splitting level in wave direction in spectral space [1]
! KCOMBFLEN - Size of communication buffer [1800000 (*8bytes) ]
! KCOMBFLEN - Size of communication buffer [1800000 (*8bytes) ] (deprecated)
! LDMPOFF - switch off message passing [false]
! LDSYNC_TRANS - switch to activate barrier before transforms [false]
! KTRANS_SYNC_LEVEL - use of synchronization/blocking [0]
Expand Down
1 change: 0 additions & 1 deletion src/trans/internal/tpm_distr.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,6 @@ MODULE TPM_DISTR
INTEGER(KIND=JPIM) :: MYPROC ! My processor number
INTEGER(KIND=JPIM) :: MYSETW ! My set number in wave direction (spectral space)
INTEGER(KIND=JPIM) :: MYSETV ! My set number in field direction(S.S and F.S)
INTEGER(KIND=JPIM) :: NCOMBFLEN ! Size of communication buffer

INTEGER(KIND=JPIM) :: MTAGLETR ! Tag
INTEGER(KIND=JPIM) :: MTAGML ! Tag
Expand Down

0 comments on commit f2754fd

Please sign in to comment.