neb working also restart. To be tested in parallel. To be improved anyway.

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@7182 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
marsamos 2010-11-01 21:02:42 +00:00
parent fb0db1abbb
commit a4a0b23e1b
10 changed files with 106 additions and 256 deletions

View File

@ -24,7 +24,8 @@ path_io_routines.o \
path_opt_routines.o \
path_reparametrisation.o \
path_variables.o \
set_defaults.o
set_defaults.o \
stop_run_path.o
QEMODS=../Modules/libqemod.a
PWOBJS= ../PW/libpw.a

View File

@ -107,7 +107,7 @@ SUBROUTINE compute_fes_grads( fii, lii, stat )
!
! ... calculation of the mean-force
!
tcpu = get_clock( 'PWSCF' )
tcpu = get_clock( 'sm' )
!
IF ( nimage > 1 ) THEN
!

View File

@ -252,7 +252,7 @@ SUBROUTINE compute_scf( fii, lii, stat )
!
CALL clean_pw( .FALSE. )
!
tcpu = get_clock( 'PWSCF' )
tcpu = get_clock( 'SM' )
!
IF ( nimage > 1 ) THEN
!

View File

@ -48,9 +48,10 @@ SUBROUTINE ioneb(xmlinput,attr)
lsmd, &
restart
!
USE path_variables, ONLY : nstep_path, lsteep_des, lquick_min, &
USE path_variables, ONLY : lsteep_des, lquick_min, &
lbroyden, lbroyden2, &
llangevin, &
nstep_path_ => nstep_path, &
ds_ => ds, &
use_masses_ => use_masses, &
CI_scheme_ => CI_scheme, &
@ -70,7 +71,7 @@ SUBROUTINE ioneb(xmlinput,attr)
wfcdir, prefix, etot_conv_thr, forc_conv_thr, &
wf_collect
USE input_parameters, ONLY : &
USE input_parameters, ONLY : nstep_path, string_method, &
num_of_images, path_thr, CI_scheme, opt_scheme, &
use_masses, first_last_opt, temp_req, k_max, &
k_min, ds, use_freezing, fixed_tan
@ -96,22 +97,7 @@ SUBROUTINE ioneb(xmlinput,attr)
CHARACTER (len=50) :: arg
!
!
!
! ... all namelists are read
!
! IF ( xmlinput ) THEN
! CALL read_xml ('PW', 1 , attr = attr )
! ELSE
write(0,*) "before read_namelist"
! CALL read_namelists( 'SM' )
write(0,*) "after read_namelist"
! ENDIF
!
!
!-----------------------------
! devono andare dopo il call a iosys
!---------------------------
SELECT CASE(trim( calculation ))
SELECT CASE(trim( string_method ))
!
CASE( 'neb' )
!
@ -123,12 +109,11 @@ SELECT CASE(trim( calculation ))
!
CASE DEFAULT
!
! CALL errore( 'iosys', 'calculation ' // &
! & trim( calculation ) // ' not implemented', 1 )
CALL errore( 'ioneb', 'string_method ' // &
& trim( string_method ) // ' not implemented', 1 )
!
END SELECT
!
!
SELECT CASE( trim( restart_mode ) )
CASE( 'from_scratch' )
!
@ -140,34 +125,32 @@ SELECT CASE(trim( calculation ))
!
! ... "path" specific
!
restart = .false.
restart = .true.
!
ENDIF
!
CASE DEFAULT
!
CALL errore( 'iosys', &
CALL errore( 'ioneb', &
& 'unknown restart_mode ' // trim( restart_mode ), 1 )
!
END SELECT
!
IF ( lpath ) THEN
!
write(0,*) "if lpath"
IF( io_level < 0) CALL errore ( 'iosys', &
IF( io_level < 0) CALL errore ( 'ioneb', &
'NEB, SMD do not work with "disk_io" set to "none"', 1)
!
nstep_path = nstep
!
IF ( num_of_images < 2 ) &
CALL errore( 'iosys', 'calculation=' // trim( calculation ) // &
CALL errore( 'ioneb', 'calculation=' // trim( calculation ) // &
& ': num_of_images must be at least 2', 1 )
!
IF ( ( CI_scheme /= "no-CI" ) .and. &
( CI_scheme /= "auto" ) .and. &
( CI_scheme /= "manual" ) ) THEN
!
CALL errore( 'iosys', 'calculation=' // trim( calculation ) // &
CALL errore( 'ioneb', 'calculation=' // trim( calculation ) // &
& ': unknown CI_scheme', 1 )
!
ENDIF
@ -182,26 +165,21 @@ write(0,*) "if lpath"
SELECT CASE( opt_scheme )
CASE( "sd" )
!
write(0,*) "case sd"
lsteep_des = .true.
!
CASE( "quick-min" )
write(0,*) "case quick-min"
!
lquick_min = .true.
!
CASE( "broyden" )
!
write(0,*) "case broyden"
lbroyden = .true.
!
CASE( "broyden2" )
write(0,*) "case broyden2"
!
lbroyden2 = .true.
!
CASE( "langevin" )
write(0,*) "case langevin"
!
llangevin = .true.
!
@ -232,6 +210,7 @@ write(0,*) "case langevin"
!
! ... "path"-optimization variables
!
nstep_path_ = nstep_path
ds_ = ds
num_of_images_ = num_of_images
first_last_opt_ = first_last_opt
@ -247,51 +226,25 @@ write(0,*) "case langevin"
!
! ... read following cards
!
! ALLOCATE( ityp( nat_ ) )
! ALLOCATE( tau( 3, nat_ ) )
! ALLOCATE( force( 3, nat_ ) )
! ALLOCATE( if_pos( 3, nat_ ) )
! ALLOCATE( extfor( 3, nat_ ) )
! IF ( tfixed_occ ) THEN
! IF ( nspin_ == 4 ) THEN
! ALLOCATE( f_inp( nbnd_, 1 ) )
! ELSE
! ALLOCATE( f_inp( nbnd_, nspin_ ) )
! ENDIF
! ENDIF
!
! IF ( tefield ) ALLOCATE( forcefield( 3, nat_ ) )
!
!write(0,*) "before read cards pw"
! CALL read_cards_pw ( psfile, tau_format, xmlinput )
!write(0,*) "after read cards pw"
!
! ... set up atomic positions and crystal lattice
!
! ... "path" optimizations specific
!
DO image = 1, num_of_images_
!
! ... "path" optimizations specific
tau = reshape( pos(1:3*nat_,image), (/ 3 , nat_ /) )
!
DO image = 1, num_of_images_
!
tau = reshape( pos(1:3*nat_,image), (/ 3 , nat_ /) )
!
CALL convert_tau ( tau_format, nat_, tau)
!
! ... note that this positions array is in Bohr
!
pos(1:3*nat_,image) = reshape( tau, (/ 3 * nat_ /) ) * alat
!
ENDDO
CALL convert_tau ( tau_format, nat_, tau)
!
! ... note that this positions array is in Bohr
!
pos(1:3*nat_,image) = reshape( tau, (/ 3 * nat_ /) ) * alat
!
ENDDO
!
!
! CALL verify_tmpdir( tmp_dir )
write(0,*) "before verify neb dir"
CALL verify_neb_tmpdir( tmp_dir )
write(0,*) "after verify neb dir"
!
! uuuu questo bisogna vedere
!
!
RETURN
!
END SUBROUTINE ioneb
@ -346,7 +299,6 @@ SUBROUTINE verify_neb_tmpdir( tmp_dir )
ENDIF
!
ELSE
write(0,*) "verify neb dir ok"
!
! ... if starting from scratch all temporary files are removed
! ... from tmp_dir ( only by the master node )

View File

@ -107,17 +107,17 @@ path_reparametrisation.o : path_variables.o
path_variables.o : ../Modules/kind.o
set_defaults.o : ../Modules/control_flags.o
set_defaults.o : ../Modules/input_parameters.o
stop_run.o : ../Modules/constraints_module.o
stop_run.o : ../Modules/control_flags.o
stop_run.o : ../Modules/environment.o
stop_run.o : ../Modules/image_io_routines.o
stop_run.o : ../Modules/input_parameters.o
stop_run.o : ../Modules/io_files.o
stop_run.o : ../Modules/io_global.o
stop_run.o : ../Modules/mm_dispersion.o
stop_run.o : ../Modules/mp_global.o
stop_run.o : ../PW/buffers.o
stop_run.o : ../PW/pwcom.o
stop_run_path.o : ../Modules/constraints_module.o
stop_run_path.o : ../Modules/control_flags.o
stop_run_path.o : ../Modules/environment.o
stop_run_path.o : ../Modules/image_io_routines.o
stop_run_path.o : ../Modules/input_parameters.o
stop_run_path.o : ../Modules/io_files.o
stop_run_path.o : ../Modules/io_global.o
stop_run_path.o : ../Modules/mm_dispersion.o
stop_run_path.o : ../Modules/mp_global.o
stop_run_path.o : ../PW/buffers.o
stop_run_path.o : ../PW/pwcom.o
string_methods.o : ../Modules/check_stop.o
string_methods.o : ../Modules/control_flags.o
string_methods.o : ../Modules/environment.o

View File

@ -37,7 +37,7 @@ MODULE path_io_routines
SUBROUTINE path_summary()
!-----------------------------------------------------------------------
!
USE input_parameters, ONLY : restart_mode, calculation, opt_scheme
USE input_parameters, ONLY : restart_mode, string_method, opt_scheme
USE control_flags, ONLY : lneb, lsmd
USE path_variables, ONLY : climbing, nstep_path, num_of_images, &
path_length, path_thr, ds, use_masses, &
@ -65,11 +65,11 @@ MODULE path_io_routines
nim_char = int_to_char( num_of_images )
!
WRITE( iunpath, * )
WRITE( iunpath, summary_fmt ) "calculation", TRIM( calculation )
WRITE( iunpath, summary_fmt ) "string_method", TRIM( string_method )
WRITE( iunpath, summary_fmt ) "restart_mode", TRIM( restart_mode )
WRITE( iunpath, summary_fmt ) "opt_scheme", TRIM( opt_scheme )
WRITE( iunpath, summary_fmt ) "num_of_images", TRIM( nim_char )
WRITE( iunpath, summary_fmt ) "nstep", TRIM( nstep_path_char )
WRITE( iunpath, summary_fmt ) "nstep_path", TRIM( nstep_path_char )
WRITE( iunpath, summary_fmt ) "CI_scheme", TRIM( CI_scheme )
!
WRITE( UNIT = iunpath, &

View File

@ -14,11 +14,13 @@ SUBROUTINE set_defaults()
!
USE control_flags, ONLY : &
lscf, &
lpath
lpath, &
lmd
lscf = .true.
lpath = .true.
! lmd = .true.
full_phs_path_flag = .true.
!
END SUBROUTINE set_defaults

View File

@ -1,156 +0,0 @@
!
! Copyright (C) 2001-2009 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,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!----------------------------------------------------------------------------
SUBROUTINE stop_run( flag )
!----------------------------------------------------------------------------
!
! ... Close all files and synchronize processes before stopping.
! ... Called at the end of the run with flag = .TRUE. (removes 'restart')
! ... or during execution with flag = .FALSE. (does not remove 'restart')
!
USE io_global, ONLY : ionode
USE mp_global, ONLY : nimage, mp_global_end
USE environment, ONLY : environment_end
! USE control_flags, ONLY : lpath, twfcollect, lconstrain, &
! lcoarsegrained, io_level, llondon
USE control_flags, ONLY : lpath, twfcollect, lconstrain, &
io_level, llondon
USE io_files, ONLY : iunwfc, iunigk, iunefield, iunefieldm,&
iunefieldp, iuntmp
USE buffers, ONLY : close_buffer
! USE path_variables, ONLY : path_deallocation
USE image_io_routines, ONLY : io_image_stop
USE london_module, ONLY : dealloca_london
USE constraints_module, ONLY : deallocate_constraint
! USE metadyn_vars, ONLY : deallocate_metadyn_vars
USE input_parameters, ONLY : deallocate_input_parameters
USE bp, ONLY : lelfield
!
IMPLICIT NONE
!
LOGICAL, INTENT(IN) :: flag
LOGICAL :: exst, opnd, flag2
!
!
#if defined (EXX)
flag2 = lpath .or. nimage > 1
#else
flag2 = lpath
#endif
IF ( flag2 ) THEN
!
CALL io_image_stop()
!
ELSE
!
! ... here we write all the data required to restart
!
CALL punch( 'all' )
!
END IF
!
! ... iunwfc contains wavefunctions and is kept open during
! ... the execution - close the file and save it (or delete it
! ... if the wavefunctions are already stored in the .save file)
!
IF ( flag .AND. ( io_level < 0 .OR. twfcollect ) ) THEN
!
call close_buffer ( iunwfc, 'DELETE' )
!
ELSE
!
call close_buffer ( iunwfc, 'KEEP' )
!
END IF
!
IF (flag .and. .not. flag2 ) THEN
CALL seqopn( iuntmp, 'restart', 'UNFORMATTED', exst )
CLOSE( UNIT = iuntmp, STATUS = 'DELETE' )
ENDIF
IF ( flag .AND. ionode ) THEN
!
! ... all other files must be reopened and removed
!
CALL seqopn( iuntmp, 'update', 'FORMATTED', exst )
CLOSE( UNIT = iuntmp, STATUS = 'DELETE' )
!
CALL seqopn( iuntmp, 'para', 'FORMATTED', exst )
CLOSE( UNIT = iuntmp, STATUS = 'DELETE' )
!
END IF
!
! ... close unit for electric field if needed
!
IF ( lelfield ) THEN
!
INQUIRE( UNIT = iunefield, OPENED = opnd )
IF ( opnd ) CLOSE( UNIT = iunefield, STATUS = 'KEEP' )
!
INQUIRE( UNIT = iunefieldm, OPENED = opnd )
IF ( opnd ) CLOSE( UNIT = iunefieldm, STATUS = 'KEEP' )
!
INQUIRE( UNIT = iunefieldp, OPENED = opnd )
IF ( opnd ) CLOSE( UNIT = iunefieldp, STATUS = 'KEEP' )
!
END IF
!
! ... iunigk is kept open during the execution - close and remove
!
INQUIRE( UNIT = iunigk, OPENED = opnd )
!
IF ( opnd ) CLOSE( UNIT = iunigk, STATUS = 'DELETE' )
!
CALL print_clock_pw()
!
CALL environment_end( 'NEB' )
!
CALL mp_global_end ()
!
CALL clean_pw( .TRUE. )
!
CALL deallocate_bp_efield()
!
CALL deallocate_input_parameters ()
!
IF ( llondon ) CALL dealloca_london()
!
IF ( lconstrain ) CALL deallocate_constraint()
!
! IF ( lcoarsegrained ) CALL deallocate_metadyn_vars()
!
! IF ( lpath ) CALL path_deallocation()
!
IF ( flag ) THEN
!
STOP
!
ELSE
!
STOP 1
!
END IF
!
END SUBROUTINE stop_run
!
!----------------------------------------------------------------------------
SUBROUTINE closefile()
!----------------------------------------------------------------------------
!
USE io_global, ONLY : stdout
!
! ... Close all files and synchronize processes before stopping
! ... Called by "sigcatch" when it receives a signal
!
WRITE( stdout,'(5X,"Signal Received, stopping ... ")')
!
CALL stop_run( .FALSE. )
!
RETURN
!
END SUBROUTINE closefile

55
NEB/stop_run_path.f90 Normal file
View File

@ -0,0 +1,55 @@
!
! Copyright (C) 2001-2009 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,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!----------------------------------------------------------------------------
SUBROUTINE stop_run_path( flag )
!----------------------------------------------------------------------------
!
! ... Close all files and synchronize processes before stopping.
! ... Called at the end of the run with flag = .TRUE. (removes 'restart')
! ... or during execution with flag = .FALSE. (does not remove 'restart')
!
USE io_global, ONLY : ionode
USE mp_global, ONLY : nimage, mp_global_end
USE environment, ONLY : environment_end
USE control_flags, ONLY : lpath, twfcollect, lconstrain, &
io_level, llondon
USE io_files, ONLY : iunwfc, iunigk, iunefield, iunefieldm,&
iunefieldp, iuntmp
USE buffers, ONLY : close_buffer
USE path_variables, ONLY : path_deallocation
USE image_io_routines, ONLY : io_image_stop
USE london_module, ONLY : dealloca_london
USE constraints_module, ONLY : deallocate_constraint
USE input_parameters, ONLY : deallocate_input_parameters
USE bp, ONLY : lelfield
!
IMPLICIT NONE
!
LOGICAL, INTENT(IN) :: flag
LOGICAL :: exst, opnd, flag2
!
!
!
!
CALL io_image_stop()
!
! call pwscf stop run routine, close files and deallocate arrays
!
CALL stop_run( flag )
!
CALL path_deallocation()
!
IF ( .not. flag ) THEN
!
STOP 1
!
END IF
!
END SUBROUTINE stop_run_path
!
!----------------------------------------------------------------------------

View File

@ -14,13 +14,13 @@ PROGRAM sm
USE io_global, ONLY : stdout, ionode, ionode_id
USE parameters, ONLY : ntypx, npk, lmaxx
USE control_flags, ONLY : conv_elec, conv_ions, lpath, gamma_only
USE environment, ONLY : environment_start
USE environment, ONLY : environment_start, environment_end
USE path_variables, ONLY : conv_path
USE check_stop, ONLY : check_stop_init
USE path_base, ONLY : initialize_path, search_mep
USE path_io_routines, ONLY : path_summary
USE image_io_routines, ONLY : io_image_start
USE mp_global, ONLY : mp_startup, mp_bcast
USE mp_global, ONLY : mp_startup, mp_bcast, mp_global_end
USE read_namelists_module, ONLY : read_namelists
!
USE iotk_module, ONLY : iotk_attlenx
@ -66,32 +66,24 @@ PROGRAM sm
call mp_bcast(xmlinput,ionode_id)
call mp_bcast(attr,ionode_id)
!
write(0,*) "xmlinput: ", xmlinput
IF( xmlinput ) THEN
CALL read_xml( 'PW', attr )
write(0,*) "check 2"
ELSE
CALL read_namelists('SM')
write(0,*) "check 2"
ENDIF
!
CALL set_defaults()
write(0,*) "check 3"
!
CALL iosys(xmlinput,attr)
write(0,*) "check 4"
!
!
CALL ioneb(xmlinput,attr)
write(0,*) "check 5"
! ... close_input_file(xmlinput)
!
IF( ionode ) CALL close_input_file(xmlinput)
!
! END INPUT RELATED
!
write(0,*) "after ioneb"
!
CALL check_stop_init()
!
@ -103,7 +95,11 @@ write(0,*) "after ioneb"
!
CALL search_mep()
!
CALL stop_run( conv_path )
CALL stop_run_path( conv_path )
!
CALL environment_end( 'SM' )
!
CALL mp_global_end()
!
STOP
!