Some cleanup

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9802 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2013-01-18 17:03:34 +00:00
parent b50b8f67bd
commit fd0b18fea2
8 changed files with 40 additions and 54 deletions

View File

@ -37,7 +37,7 @@ SUBROUTINE compute_scf( fii, lii, stat )
istep_path, frozen, num_of_images, &
first_last_opt
USE io_global, ONLY : stdout, ionode, ionode_id, meta_ionode
USE mp_image_global_module, ONLY : inter_image_comm, intra_image_comm, &
USE mp_image_global_module, ONLY : inter_image_comm, intra_image_comm, &
my_image_id, nimage, root_image
USE mp, ONLY : mp_bcast, mp_barrier, mp_sum, mp_min
USE path_io_routines, ONLY : new_image_init, get_new_image, &
@ -134,7 +134,7 @@ SUBROUTINE compute_scf( fii, lii, stat )
! ... only the first cpu initializes the file needed by parallelization
! ... among images
!
IF ( meta_ionode ) CALL new_image_init( fii_, tmp_dir_saved )
IF ( meta_ionode ) CALL new_image_init( nimage, fii_, tmp_dir_saved )
!
image = fii_ + my_image_id
!
@ -152,7 +152,7 @@ SUBROUTINE compute_scf( fii, lii, stat )
!
! ... the new image is obtained (by ionode only)
!
CALL get_new_image( image, tmp_dir_saved )
CALL get_new_image( nimage, image, tmp_dir_saved )
!
CALL mp_bcast( image, ionode_id, intra_image_comm )
!
@ -394,12 +394,6 @@ SUBROUTINE compute_scf( fii, lii, stat )
CLOSE( UNIT = iunupdate, STATUS = 'KEEP' )
!
END IF
!
! ... input values are restored at the end of each iteration
! ... ( they are modified by init_run ) - OBSOLETE?
!
! starting_pot = 'atomic'
! starting_wfc = 'file'
!
ethr = diago_thr_init
!

View File

@ -89,7 +89,6 @@ SUBROUTINE ioneb()
!
END SELECT
!
!
!
! check da mettere dopo iosys del pw
!
@ -189,10 +188,9 @@ SUBROUTINE verify_neb_tmpdir( tmp_dir )
!
USE wrappers, ONLY : f_mkdir
USE path_input_parameters_module, ONLY : restart_mode
USE io_files, ONLY : prefix, xmlpun, &
delete_if_present
USE io_files, ONLY : prefix, xmlpun, delete_if_present
USE path_variables, ONLY : num_of_images
USE mp_image_global_module, ONLY : mpime, nproc, nimage
USE mp_image_global_module, ONLY : mpime, nproc
USE io_global, ONLY : meta_ionode
USE mp, ONLY : mp_barrier
USE xml_io_base, ONLY : copy_file

View File

@ -43,7 +43,7 @@ neb.o : ../../Modules/check_stop.o
neb.o : ../../Modules/environment.o
neb.o : ../../Modules/image_io_routines.o
neb.o : ../../Modules/io_global.o
neb.o : ../../Modules/mp_global.o
neb.o : ../../Modules/mp.o
neb.o : ../../Modules/mp_image_global_module.o
neb.o : ../../Modules/open_close_input_file.o
neb.o : ../../Modules/read_cards.o
@ -91,7 +91,6 @@ path_io_routines.o : ../../Modules/io_global.o
path_io_routines.o : ../../Modules/ions_base.o
path_io_routines.o : ../../Modules/kind.o
path_io_routines.o : ../../Modules/mp.o
path_io_routines.o : ../../Modules/mp_image_global_module.o
path_io_routines.o : path_formats.o
path_io_routines.o : path_input_parameters_module.o
path_io_routines.o : path_io_units_module.o
@ -136,6 +135,5 @@ stop_run_path.o : ../../Modules/environment.o
stop_run_path.o : ../../Modules/image_io_routines.o
stop_run_path.o : ../../Modules/io_global.o
stop_run_path.o : ../../Modules/mp_global.o
stop_run_path.o : ../../Modules/mp_image_global_module.o
stop_run_path.o : path_io_units_module.o
stop_run_path.o : path_variables.o

View File

@ -1,5 +1,5 @@
!
! Copyright (C) 2011 Quantum ESPRESSO group
! Copyright (C) 2011-2013 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
@ -15,8 +15,7 @@ PROGRAM neb
USE environment, ONLY : environment_start, environment_end
USE check_stop, ONLY : check_stop_init
USE image_io_routines, ONLY : io_image_start
USE mp_global, ONLY : mp_bcast, mp_rank, mp_start
!
USE mp, ONLY : mp_bcast, mp_rank, mp_start
USE mp_image_global_module, ONLY : mp_image_startup, world_comm, &
me_image, nimage
USE iotk_module, ONLY : iotk_open_read, iotk_close_read, iotk_attlenx
@ -60,6 +59,8 @@ PROGRAM neb
CALL mp_start(nproc,mpime,neb_comm)
CALL mp_image_startup (root,neb_comm)
CALL engine_mp_start()
!!! CALL mp_startup ( start_images=.true. )
!!! IF ( nimage > 1 ) CALL io_image_start( )
#endif
CALL environment_start ( 'NEB' )
!
@ -72,6 +73,7 @@ PROGRAM neb
!
engine_prefix = "pw_"
!
!!!CALL mp_bcast(parsing_file_name,root,world_comm)
CALL mp_bcast(parsing_file_name,root,neb_comm)
CALL mp_bcast(lfound_parsing_file,root,neb_comm)
!
@ -86,7 +88,7 @@ PROGRAM neb
WRITE(0,*) "Searching argument -input_images or --input_images"
IF ( mpime == root ) CALL input_images_getarg &
(input_images,lfound_input_images)
CALL mp_bcast(input_images,root,neb_comm)
CALL mp_bcast(input_images,root, neb_comm)
CALL mp_bcast(lfound_input_images,root,neb_comm)
!
IF (.not.lfound_input_images) CALL errore('string_methods', &
@ -140,33 +142,30 @@ PROGRAM neb
CALL read_xml('PW', attr = attr )
CALL iotk_close_read(unit_tmp)
endif
!
CALL iosys()
!
CALL engine_to_path_pos(i)
!
enddo
!
CALL path_to_engine_fix_atom_pos()
!
CALL ioneb()
!
CALL set_engine_io_units()
!
! END INPUT RELATED
!
CALL check_stop_init()
!
CALL io_image_start()
!
CALL initialize_path()
!
CALL deallocate_path_input_ions()
!
CALL path_summary()
!
CALL search_mep()
!
CALL stop_run_path( conv_path )
!
!
STOP
!
END PROGRAM neb

View File

@ -55,26 +55,26 @@ MODULE path_base
SUBROUTINE initialize_path()
!-----------------------------------------------------------------------
!
USE control_flags, ONLY : conv_elec
USE ions_base, ONLY : amass, ityp
USE io_files, ONLY : prefix, tmp_dir
USE mp_image_global_module, ONLY : nimage
USE path_input_parameters_module, ONLY : pos_ => pos, &
climbing_ => climbing, &
input_images, nstep_path_ => nstep_path
USE path_input_parameters_module, ONLY : restart_mode
USE path_variables, ONLY : fix_atom_pos
USE path_input_parameters_module, ONLY : nat
USE control_flags, ONLY : conv_elec
USE ions_base, ONLY : amass, ityp
USE io_files, ONLY : prefix, tmp_dir
USE path_io_units_module, ONLY : path_file, dat_file, crd_file, &
int_file, xyz_file, axsf_file, broy_file
USE path_variables, ONLY : fix_atom_pos
USE path_variables, ONLY : climbing, pos, istep_path, nstep_path, &
dim1, num_of_images, pes, grad_pes, mass, &
use_masses, tangent, error, path_length, &
deg_of_freedom, frozen, use_freezing, k, &
k_min, tune_load_balance, grad, posold, &
elastic_grad, pending_image, first_last_opt
USE mp_image_global_module, ONLY : nimage
USE path_io_routines, ONLY : read_restart
USE path_variables, ONLY : path_allocation
USE path_io_routines, ONLY : read_restart
USE path_io_units_module, ONLY : path_file, dat_file, crd_file, &
int_file, xyz_file, axsf_file, broy_file
!
IMPLICIT NONE
!
@ -749,7 +749,7 @@ MODULE path_base
SUBROUTINE born_oppenheimer_pes( stat )
!------------------------------------------------------------------------
!
USE path_variables, ONLY : nim => num_of_images, &
USE path_variables, ONLY : num_of_images, &
pending_image, istep_path, pes, &
first_last_opt, Emin, Emax, Emax_index
!
@ -763,12 +763,12 @@ MODULE path_base
IF ( istep_path == 0 .OR. first_last_opt ) THEN
!
fii = 1
lii = nim
lii = num_of_images
!
ELSE
!
fii = 2
lii = nim - 1
lii = num_of_images - 1
!
END IF
!
@ -778,9 +778,9 @@ MODULE path_base
!
IF ( .NOT. stat ) RETURN
!
Emin = MINVAL( pes(1:nim) )
Emax = MAXVAL( pes(1:nim) )
Emax_index = MAXLOC( pes(1:nim), 1 )
Emin = MINVAL( pes(1:num_of_images) )
Emax = MAXVAL( pes(1:num_of_images) )
Emax_index = MAXLOC( pes(1:num_of_images), 1 )
!
RETURN
!
@ -790,7 +790,7 @@ MODULE path_base
SUBROUTINE fe_profile()
!------------------------------------------------------------------------
!
USE path_variables, ONLY : nim => num_of_images
USE path_variables, ONLY : num_of_images
USE path_variables, ONLY : pos, pes, grad_pes, &
Emin, Emax, Emax_index
!
@ -801,16 +801,16 @@ MODULE path_base
!
pes(:) = 0.0_DP
!
DO i = 2, nim
DO i = 2, num_of_images
!
pes(i) = pes(i-1) + 0.5_DP*( ( pos(:,i) - pos(:,i-1) ) .dot. &
( grad_pes(:,i) + grad_pes(:,i-1) ) )
!
END DO
!
Emin = MINVAL( pes(1:nim) )
Emax = MAXVAL( pes(1:nim) )
Emax_index = MAXLOC( pes(1:nim), 1 )
Emin = MINVAL( pes(1:num_of_images) )
Emax = MAXVAL( pes(1:num_of_images) )
Emax_index = MAXLOC( pes(1:num_of_images), 1 )
!
RETURN
!

View File

@ -821,7 +821,7 @@ MODULE path_io_routines
END SUBROUTINE write_output
!
!-----------------------------------------------------------------------
SUBROUTINE new_image_init( fii, outdir )
SUBROUTINE new_image_init( nimage, fii, outdir )
!-----------------------------------------------------------------------
!
! ... this subroutine initializes the file needed for the
@ -830,11 +830,10 @@ MODULE path_io_routines
USE path_io_units_module, ONLY : iunnewimage
USE io_files, ONLY : prefix
USE path_variables, ONLY : tune_load_balance
USE mp_image_global_module, ONLY : nimage
!
IMPLICIT NONE
!
INTEGER, INTENT(IN) :: fii
INTEGER, INTENT(IN) :: nimage, fii
CHARACTER(LEN=*), INTENT(IN) :: outdir
!
!
@ -852,7 +851,7 @@ MODULE path_io_routines
END SUBROUTINE new_image_init
!
!-----------------------------------------------------------------------
SUBROUTINE get_new_image( image, outdir )
SUBROUTINE get_new_image( nimage, image, outdir )
!-----------------------------------------------------------------------
!
! ... this subroutine is used to get the new image to work on
@ -862,10 +861,10 @@ MODULE path_io_routines
USE io_files, ONLY : iunnewimage, iunlock, prefix
USE io_global, ONLY : ionode
USE path_variables, ONLY : tune_load_balance
USE mp_image_global_module, ONLY : nimage
!
IMPLICIT NONE
!
INTEGER, INTENT(IN) :: nimage
INTEGER, INTENT(INOUT) :: image
CHARACTER(LEN=*), INTENT(IN) :: outdir
!

View File

@ -14,11 +14,10 @@ SUBROUTINE stop_run_path( lflag )
! ... or during execution with flag = .FALSE. (does not remove 'restart')
!
USE io_global, ONLY : ionode, stdout
USE mp_global, ONLY : mp_global_end
USE mp_image_global_module, ONLY : nimage
USE mp_global, ONLY : mp_global_end
USE environment, ONLY : environment_end
USE path_variables, ONLY : path_deallocation
USE image_io_routines, ONLY : io_image_stop
USE image_io_routines, ONLY : io_image_stop
USE path_io_units_module, ONLY : iunpath
!
IMPLICIT NONE

View File

@ -901,7 +901,6 @@ move_ions.o : newd.o
move_ions.o : pwcom.o
move_ions.o : symm_base.o
ms2.o : ../../Modules/mp.o
ms2.o : ../../Modules/mp_global.o
n_plane_waves.o : ../../Modules/kind.o
n_plane_waves.o : ../../Modules/mp.o
n_plane_waves.o : ../../Modules/mp_global.o