Skip to content

Commit

Permalink
mp_global replaced with more apropriate modules in Modules/
Browse files Browse the repository at this point in the history
Corrections by Axel to last commit


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@10534 c92efa57-630b-4861-b058-cf58834340f0
  • Loading branch information
giannozz committed Oct 13, 2013
1 parent eabe5f6 commit 51ad80d
Show file tree
Hide file tree
Showing 17 changed files with 287 additions and 109 deletions.
14 changes: 7 additions & 7 deletions Modules/becmod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -77,8 +77,8 @@ MODULE becmod
SUBROUTINE calbec_bec_type ( npw, beta, psi, betapsi, nbnd )
!-----------------------------------------------------------------------
!_
USE mp_global, ONLY: intra_bgrp_comm
USE mp, ONLY: mp_size, mp_rank, mp_get_comm_null
USE mp_bands, ONLY: intra_bgrp_comm
USE mp, ONLY: mp_size, mp_rank, mp_get_comm_null
!
IMPLICIT NONE
COMPLEX (DP), INTENT (in) :: beta(:,:), psi(:,:)
Expand Down Expand Up @@ -141,7 +141,7 @@ END SUBROUTINE calbec_bec_type
!-----------------------------------------------------------------------
SUBROUTINE calbec_gamma_nocomm ( npw, beta, psi, betapsi, nbnd )
!-----------------------------------------------------------------------
USE mp_global, ONLY: intra_bgrp_comm
USE mp_bands, ONLY: intra_bgrp_comm
IMPLICIT NONE
COMPLEX (DP), INTENT (in) :: beta(:,:), psi(:,:)
REAL (DP), INTENT (out) :: betapsi(:,:)
Expand Down Expand Up @@ -223,8 +223,8 @@ SUBROUTINE calbec_k ( npw, beta, psi, betapsi, nbnd )
! ... matrix times matrix with summation index (k=1,npw) running on
! ... G-vectors or PWs : betapsi(i,j) = \sum_k beta^*(i,k) psi(k,j)
!
USE mp_global, ONLY : intra_bgrp_comm
USE mp, ONLY : mp_sum
USE mp_bands, ONLY : intra_bgrp_comm
USE mp, ONLY : mp_sum

IMPLICIT NONE
COMPLEX (DP), INTENT (in) :: beta(:,:), psi(:,:)
Expand Down Expand Up @@ -283,8 +283,8 @@ SUBROUTINE calbec_nc ( npw, beta, psi, betapsi, nbnd )
! ... betapsi(i,1,j) = \sum_k=1,npw beta^*(i,k) psi(k,j)
! ... betapsi(i,2,j) = \sum_k=1,npw beta^*(i,k) psi(k+npwx,j)
!
USE mp_global, ONLY : intra_bgrp_comm
USE mp, ONLY : mp_sum
USE mp_bands, ONLY : intra_bgrp_comm
USE mp, ONLY : mp_sum

IMPLICIT NONE
COMPLEX (DP), INTENT (in) :: beta(:,:), psi(:,:)
Expand Down
2 changes: 1 addition & 1 deletion Modules/check_stop.f90
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ FUNCTION check_stop_now( inunit )
!-----------------------------------------------------------------------
!
USE mp, ONLY : mp_bcast
USE mp_global, ONLY : intra_image_comm
USE mp_images, ONLY : intra_image_comm
USE io_global, ONLY : ionode, ionode_id, meta_ionode, stdout
USE io_files, ONLY : tmp_dir, exit_file, iunexit
#if defined __TRAP_SIGUSR1
Expand Down
8 changes: 4 additions & 4 deletions Modules/clocks.f90
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ SUBROUTINE start_clock( label )
USE kinds, ONLY : DP
USE io_global, ONLY : stdout
#if defined (__TRACE)
USE mp_global, ONLY : mpime
USE mp_world, ONLY : mpime
#endif
USE mytime, ONLY : nclock, clock_label, notrunning, no, maxclock, &
t0cpu, t0wall, trace_depth
Expand Down Expand Up @@ -164,7 +164,7 @@ SUBROUTINE stop_clock( label )
USE kinds, ONLY : DP
USE io_global, ONLY : stdout
#if defined (__TRACE)
USE mp_global, ONLY : mpime
USE mp_world, ONLY : mpime
#endif
USE mytime, ONLY : no, nclock, clock_label, cputime, walltime, &
notrunning, called, t0cpu, t0wall, trace_depth
Expand Down Expand Up @@ -285,7 +285,7 @@ SUBROUTINE print_this_clock( n )
! ... See comments below about parallel case
!
! USE mp, ONLY : mp_max
! USE mp_global, ONLY : intra_image_comm, my_image_id
! USE mp_images, ONLY : intra_image_comm, my_image_id
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -429,7 +429,7 @@ FUNCTION get_clock( label )
! ... See comments in subroutine print_this_clock about parallel case
!
! USE mp, ONLY : mp_max
! USE mp_global, ONLY : intra_image_comm
! USE mp_images, ONLY : intra_image_comm
!
IMPLICIT NONE
!
Expand Down
2 changes: 1 addition & 1 deletion Modules/compute_dipole.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ SUBROUTINE compute_dipole( nnr, nspin, rho, r0, dipole, quadrupole )
USE kinds, ONLY : DP
USE cell_base, ONLY : at, bg, alat, omega
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
Expand Down
3 changes: 2 additions & 1 deletion Modules/dspev_drv.f90
Original file line number Diff line number Diff line change
Expand Up @@ -650,7 +650,8 @@ END SUBROUTINE dspev_drv

SUBROUTINE pdsyevd_drv( tv, n, nb, s, lds, w, ortho_cntx )
USE kinds, ONLY : DP
USE mp_global, ONLY: nproc_bgrp, me_bgrp, intra_bgrp_comm,root_bgrp,ortho_comm
USE mp_bands, ONLY: nproc_bgrp, me_bgrp, intra_bgrp_comm, root_bgrp
USE mp_diag, ONLY: ortho_comm
#ifdef __ELPA
USE elpa1
#endif
Expand Down
8 changes: 6 additions & 2 deletions Modules/environment.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,12 @@ MODULE environment
USE kinds, ONLY: DP
USE io_files, ONLY: crash_file, nd_nmbr
USE io_global, ONLY: stdout, meta_ionode
USE mp_global, ONLY: me_image, my_image_id, root_image, nimage, &
nproc_image, nproc, npool, nproc_bgrp, nbgrp, get_ntask_groups
USE mp_global, ONLY: get_ntask_groups
USE mp_world, ONLY: nproc
USE mp_images, ONLY: me_image, my_image_id, root_image, nimage, &
nproc_image
USE mp_pools, ONLY: npool
USE mp_bands, ONLY: nproc_bgrp, nbgrp
USE global_version, ONLY: version_number, svn_revision

IMPLICIT NONE
Expand Down
4 changes: 2 additions & 2 deletions Modules/error_handler.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,8 @@ SUBROUTINE errore( calling_routine, message, ierr )
! ... error, unit 0 (the message will appear in the error files
! ... produced by loadleveler).
!
USE mp, ONLY : mp_abort
USE mp_global, ONLY : mpime, world_comm
USE mp, ONLY : mp_abort
USE mp_world, ONLY : mpime, world_comm
USE io_global, ONLY : stdout
USE io_files, ONLY : crash_file
#if defined(__PTRACE) && defined(__INTEL)
Expand Down
12 changes: 6 additions & 6 deletions Modules/generate_function.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ SUBROUTINE generate_gaussian( nnr, charge, spread, pos, rho )
USE constants, ONLY : sqrtpi
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -117,7 +117,7 @@ SUBROUTINE generate_gradgaussian( nnr, charge, spread, pos, gradrho )
USE constants, ONLY: sqrtpi
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -206,7 +206,7 @@ SUBROUTINE generate_exponential( nnr, spread, pos, rho )
USE kinds, ONLY : DP
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -300,7 +300,7 @@ SUBROUTINE generate_gradexponential( nnr, spread, pos, gradrho )
USE kinds, ONLY : DP
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -391,7 +391,7 @@ SUBROUTINE generate_axis( nnr, icor, pos, axis )
USE kinds, ONLY : DP
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
INTEGER, INTENT(IN) :: nnr
INTEGER, INTENT(IN) :: icor
Expand Down Expand Up @@ -463,7 +463,7 @@ SUBROUTINE generate_distance( nnr, pos, distance )
USE kinds, ONLY : DP
USE cell_base, ONLY : at, bg, alat
USE fft_base, ONLY : dfftp
USE mp_global, ONLY : me_bgrp, intra_bgrp_comm
USE mp_bands, ONLY : me_bgrp, intra_bgrp_comm
!
INTEGER, INTENT(IN) :: nnr
REAL(DP), INTENT(IN) :: pos(3)
Expand Down
2 changes: 1 addition & 1 deletion Modules/griddim.f90
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ SUBROUTINE grid_set( bg, gcut, nr1, nr2, nr3 )
! ... declare modules
USE kinds, ONLY: DP
USE mp, ONLY: mp_max, mp_min, mp_sum
USE mp_global, ONLY: me_image, nproc_image, intra_image_comm
USE mp_images, ONLY: me_image, nproc_image, intra_image_comm

IMPLICIT NONE

Expand Down
10 changes: 0 additions & 10 deletions Modules/input_parameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -264,12 +264,6 @@ MODULE input_parameters
! if memory = 'large' then QE tries to use (when implemented) algorithms using more memory
! to enhance performance.

! XXX may go away at some point
#if defined (__MS2)
LOGICAL :: MS2_enabled = .false. ! Enable the shared memory exchange in MS2
CHARACTER(len=256) :: MS2_handler = ' '! Name for the shared memory handler in MS2
#endif

NAMELIST / control / title, calculation, verbosity, restart_mode, &
nstep, iprint, isave, tstress, tprnfor, dt, ndr, ndw, outdir, &
prefix, wfcdir, max_seconds, ekin_conv_thr, etot_conv_thr, &
Expand All @@ -278,10 +272,6 @@ MODULE input_parameters
tefield2, saverho, tabps, lkpoint_dir, use_wannier, lecrpa, &
tqmmm, vdw_table_name, lorbm, memory, point_label_type

#if defined ( __MS2)
NAMELIST / control / MS2_enabled, MS2_handler
#endif

!
!=----------------------------------------------------------------------------=!
! SYSTEM Namelist Input Parameters
Expand Down
27 changes: 17 additions & 10 deletions Modules/make.depend
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ basic_algebra_routines.o : kind.o
becmod.o : control_flags.o
becmod.o : kind.o
becmod.o : mp.o
becmod.o : mp_global.o
becmod.o : mp_bands.o
becmod.o : noncol.o
becmod.o : recvec.o
bfgs_module.o : basic_algebra_routines.o
Expand All @@ -28,19 +28,19 @@ check_stop.o : io_files.o
check_stop.o : io_global.o
check_stop.o : kind.o
check_stop.o : mp.o
check_stop.o : mp_global.o
check_stop.o : mp_images.o
check_stop.o : set_signal.o
clocks.o : io_global.o
clocks.o : kind.o
clocks.o : mp_global.o
clocks.o : mp_world.o
command_line_options.o : io_global.o
command_line_options.o : mp.o
command_line_options.o : mp_world.o
compute_dipole.o : cell_base.o
compute_dipole.o : fft_base.o
compute_dipole.o : kind.o
compute_dipole.o : mp.o
compute_dipole.o : mp_global.o
compute_dipole.o : mp_bands.o
constants.o : kind.o
constraints_module.o : basic_algebra_routines.o
constraints_module.o : cell_base.o
Expand All @@ -52,7 +52,8 @@ constraints_module.o : kind.o
control_flags.o : kind.o
control_flags.o : parameters.o
dspev_drv.o : kind.o
dspev_drv.o : mp_global.o
dspev_drv.o : mp_bands.o
dspev_drv.o : mp_diag.o
electrons_base.o : constants.o
electrons_base.o : io_global.o
electrons_base.o : kind.o
Expand All @@ -64,12 +65,16 @@ environ_input.o : parameters.o
environment.o : io_files.o
environment.o : io_global.o
environment.o : kind.o
environment.o : mp_bands.o
environment.o : mp_global.o
environment.o : mp_images.o
environment.o : mp_pools.o
environment.o : mp_world.o
environment.o : version.o
error_handler.o : io_files.o
error_handler.o : io_global.o
error_handler.o : mp.o
error_handler.o : mp_global.o
error_handler.o : mp_world.o
fd_gradient.o : cell_base.o
fd_gradient.o : fft_base.o
fd_gradient.o : kind.o
Expand Down Expand Up @@ -107,13 +112,13 @@ generate_function.o : cell_base.o
generate_function.o : constants.o
generate_function.o : fft_base.o
generate_function.o : kind.o
generate_function.o : mp_global.o
generate_function.o : mp_bands.o
griddim.o : fft_scalar.o
griddim.o : fft_types.o
griddim.o : io_global.o
griddim.o : kind.o
griddim.o : mp.o
griddim.o : mp_global.o
griddim.o : mp_images.o
input_parameters.o : kind.o
input_parameters.o : parameters.o
input_parameters.o : wannier_new.o
Expand All @@ -135,11 +140,13 @@ mm_dispersion.o : io_global.o
mm_dispersion.o : ions_base.o
mm_dispersion.o : kind.o
mm_dispersion.o : mp.o
mm_dispersion.o : mp_global.o
mm_dispersion.o : mp_images.o
mm_dispersion.o : mp_world.o
mp.o : io_global.o
mp.o : kind.o
mp.o : parallel_include.o
mp_atoms.o : mp.o
mp_atoms.o : parallel_include.o
mp_bands.o : mp.o
mp_bands.o : parallel_include.o
mp_base.o : kind.o
Expand Down Expand Up @@ -368,5 +375,5 @@ xml_io_base.o : wrappers.o
zhpev_drv.o : io_global.o
zhpev_drv.o : kind.o
zhpev_drv.o : mp.o
zhpev_drv.o : mp_global.o
zhpev_drv.o : mp_diag.o
fft_scalar.o : ../include/fft_defs.h
6 changes: 3 additions & 3 deletions Modules/mm_dispersion.f90
Original file line number Diff line number Diff line change
Expand Up @@ -300,7 +300,7 @@ FUNCTION energy_london ( alat , nat , ityp , at , bg , tau )
! and scal6 is a global scaling factor
!
#if defined __MPI
USE mp_global, ONLY : me_image , nproc_image, intra_image_comm
USE mp_images, ONLY : me_image , nproc_image, intra_image_comm
USE mp, ONLY : mp_sum
#endif
!
Expand Down Expand Up @@ -414,7 +414,7 @@ FUNCTION force_london ( alat , nat , ityp , at , bg , tau )
!
!
#if defined __MPI
USE mp_global, ONLY : me_image , nproc_image , intra_image_comm
USE mp_images, ONLY : me_image , nproc_image , intra_image_comm
USE mp, ONLY : mp_sum
#endif
!
Expand Down Expand Up @@ -554,7 +554,7 @@ FUNCTION stres_london ( alat , nat , ityp , at , bg , tau , omega )
!
!
#if defined __MPI
USE mp_global, ONLY : me_image , nproc_image , intra_image_comm
USE mp_images, ONLY : me_image , nproc_image , intra_image_comm
USE mp, ONLY : mp_sum
#endif
!
Expand Down
Loading

0 comments on commit 51ad80d

Please sign in to comment.