path units and files erased from io_files, if(tapos) return added to read_cards

some aditional cleaning for neb purpose in Modules.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@7331 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
marsamos 2010-12-20 22:14:44 +00:00
parent ef857ff7d0
commit 78fd27ec7d
7 changed files with 291 additions and 1026 deletions

View File

@ -477,7 +477,7 @@ FUNCTION get_clock( label )
!
get_clock = notrunning
!
WRITE( stdout, '("get_clock: no clock for ",A12," found !")') label
WRITE( 0, '("get_clock: no clock for ",A12," found !")') label
!
RETURN
!

View File

@ -1019,74 +1019,6 @@ MODULE input_parameters
fe_step, fe_nstep, sw_nstep, eq_nstep, g_amplitude
!
! ... variables added for "path" calculations
!
!
! ... these are two auxiliary variables used in read_cards to
! ... distinguish among neb and smd done in the full phase-space
! ... or in the coarse-grained phase-space
!
LOGICAL :: full_phs_path_flag = .false.
LOGICAL :: cg_phs_path_flag = .false.
!
INTEGER :: nstep_path
!
CHARACTER(len=80) :: string_method = 'neb'
! 'neb' traditional neb as described by Jonsson
! 'sm' something else
CHARACTER(len=80) :: string_method_scheme_allowed(2)
DATA string_method_scheme_allowed / 'neb', 'sm' /
!
INTEGER :: input_images = 0
!
INTEGER :: num_of_images = 0
!
CHARACTER(len=80) :: CI_scheme = 'no-CI'
! CI_scheme = 'no-CI' | 'auto' | 'manual'
! set the Climbing Image scheme
! 'no-CI' Climbing Image is not used
! 'auto' Standard Climbing Image
! 'manual' the image is selected by hand
!
CHARACTER(len=80) :: CI_scheme_allowed(3)
DATA CI_scheme_allowed / 'no-CI', 'auto', 'manual' /
!
LOGICAL :: first_last_opt = .false.
LOGICAL :: use_masses = .false.
LOGICAL :: use_freezing = .false.
LOGICAL :: fixed_tan = .false.
!
CHARACTER(len=80) :: opt_scheme = 'quick-min'
! minimization_scheme = 'quick-min' | 'damped-dyn' |
! 'mol-dyn' | 'sd'
! set the minimization algorithm
! 'quick-min' projected molecular dynamics
! 'sd' steepest descent
! 'broyden' broyden acceleration
! 'broyden2' broyden acceleration - better ?
! 'langevin' langevin dynamics
!
CHARACTER(len=80) :: opt_scheme_allowed(5)
DATA opt_scheme_allowed / 'quick-min', 'broyden', 'broyden2', 'sd', 'langevin' /
!
REAL (DP) :: temp_req = 0.0_DP
! meaningful only when minimization_scheme = 'sim-annealing'
REAL (DP) :: ds = 1.0_DP
!
REAL (DP) :: k_max = 0.1_DP, k_min = 0.1_DP
!
REAL (DP) :: path_thr = 0.05_DP
!
!
NAMELIST / PATH / &
string_method, nstep_path, num_of_images, &
CI_scheme, opt_scheme, use_masses, &
first_last_opt, ds, k_max, k_min, temp_req, &
path_thr, fixed_tan, use_freezing
!=----------------------------------------------------------------------------=!
! CELL Namelist Input Parameters
!=----------------------------------------------------------------------------=!
@ -1306,7 +1238,6 @@ MODULE input_parameters
!
! ... variable added for NEB ( C.S. 17/10/2003 )
!
REAL(DP), ALLOCATABLE :: pos(:,:)
!
!
! ION_VELOCITIES
@ -1548,8 +1479,6 @@ CONTAINS
IF ( allocated( sp_vel ) ) DEALLOCATE( sp_vel )
IF ( allocated( rd_for ) ) DEALLOCATE( rd_for )
!
IF ( allocated( pos ) ) DEALLOCATE( pos )
IF ( allocated( climbing ) ) DEALLOCATE( climbing )
!
IF ( allocated( constr_type_inp ) ) DEALLOCATE( constr_type_inp )
IF ( allocated( constr_inp ) ) DEALLOCATE( constr_inp )

View File

@ -32,14 +32,6 @@ MODULE io_files
CHARACTER(LEN=256) :: output_drho = ' ' ! name of the file with the output drho
!
CHARACTER(LEN=5 ), PARAMETER :: crash_file = 'CRASH'
CHARACTER (LEN=256) :: &
dat_file = 'os.dat', &! file containing the enegy profile
int_file = 'os.int', &! file containing the interpolated energy profile
crd_file = 'os.crd', &! file containing path coordinates in pw.x input format
path_file = 'os.path', &! file containing informations needed to restart a path simulation
xyz_file = 'os.xyz', &! file containing coordinates of all images in xyz format
axsf_file = 'os.axsf', &! file containing coordinates of all images in axsf format
broy_file = 'os.broyden' ! file containing broyden's history
CHARACTER (LEN=261) :: &
exit_file = "os.EXIT" ! file required for a soft exit
!
@ -82,15 +74,6 @@ MODULE io_files
!
! ... "path" specific
!
INTEGER :: iunpath = 6 ! unit for string output ( stdout or what else )
INTEGER :: iunrestart = 2021 ! unit for saving the restart file ( neb_file )
INTEGER :: iundat = 2022 ! unit for saving the enegy profile
INTEGER :: iunint = 2023 ! unit for saving the interpolated energy profile
INTEGER :: iunxyz = 2024 ! unit for saving coordinates ( xyz format )
INTEGER :: iunaxsf = 2025 ! unit for saving coordinates ( axsf format )
INTEGER :: iunbroy = 2026 ! unit for saving broyden's history
INTEGER :: iuncrd = 2027 ! unit for saving coordinates in pw.x input format
!
!... finite electric field (Umari)
!
INTEGER :: iunefield = 31 ! unit to store wavefunction for calculatin electric field operator

View File

@ -176,9 +176,9 @@ CONTAINS
!
CALL card_constraints( input_line )
!
ELSEIF ( trim(card) == 'COLLECTIVE_VARS' ) THEN
! ELSEIF ( trim(card) == 'COLLECTIVE_VARS' ) THEN
!
CALL card_collective_vars( input_line )
! CALL card_collective_vars( input_line )
!
ELSEIF ( trim(card) == 'VHMEAN' ) THEN
!
@ -227,9 +227,9 @@ CONTAINS
IF ( ( prog == 'PW' ) .and. ionode ) &
WRITE( stdout,'(a)') 'Warning: card '//trim(input_line)//' ignored'
!
ELSEIF ( trim(card) == 'CLIMBING_IMAGES' ) THEN
! ELSEIF ( trim(card) == 'CLIMBING_IMAGES' ) THEN
!
CALL card_climbing_images( input_line )
! CALL card_climbing_images( input_line )
ELSEIF ( trim(card) == 'PLOT_WANNIER' ) THEN
!
@ -399,6 +399,7 @@ CONTAINS
CHARACTER(len=256) :: field_str, error_msg
!
!
IF(tapos) return
IF ( tread ) THEN
CALL errore( 'card_atomic_positions', 'two occurrences', 2 )
ENDIF
@ -413,6 +414,11 @@ CONTAINS
CALL errore( 'card_atomic_positions', 'nat out of range', nat )
ENDIF
!
!
!new
CALL allocate_input_ions(ntyp,nat)
!
!
if_pos = 1
!
sp_pos = 0
@ -439,75 +445,6 @@ CONTAINS
ENDIF
!
IF ( full_phs_path_flag ) THEN
!
IF ( allocated( pos ) ) DEALLOCATE( pos )
ALLOCATE( pos( 3*nat, num_of_images ) )
pos(:,:) = 0.0_DP
!
IF ( calculation == 'smd' .and. prog == 'CP' ) THEN
!
CALL errore( 'read_cards', &
'smd no longer implemented in CP', 1 )
!
ELSE
!
CALL read_line( input_line, end_of_file = tend )
IF ( tend ) &
CALL errore( 'read_cards', &
'end of file reading atomic positions (path)', 1 )
!
IF ( matches( "first_image", input_line ) ) THEN
!
input_images = 1
CALL path_read_images( input_images )
!
ELSE
!
CALL errore( 'read_cards', &
'first_image missing in ATOMIC_POSITION', 1 )
!
ENDIF
!
read_conf_loop: DO
!
CALL read_line( input_line, end_of_file = tend )
!
IF ( tend ) &
CALL errore( 'read_cards', 'end of file reading ' // &
& 'atomic positions (path)', input_images + 1 )
!
input_images = input_images + 1
IF ( input_images > num_of_images ) &
CALL errore( 'read_cards', &
& 'too many images in ATOMIC_POSITION', 1 )
!
IF ( matches( "intermediate_image", input_line ) ) THEN
!
CALL path_read_images( input_images )
!
ELSE
!
exit read_conf_loop
!
ENDIF
!
ENDDO read_conf_loop
!
IF ( matches( "last_image", input_line ) ) THEN
!
CALL path_read_images( input_images )
!
ELSE
!
CALL errore( 'read_cards ', &
'last_image missing in ATOMIC_POSITION', 1 )
!
ENDIF
!
ENDIF
!
ELSE
!
reader_loop : DO ia = 1,nat,1
@ -588,7 +525,6 @@ CONTAINS
ENDDO reader_loop
!
ENDIF
!
! DO is = 1, ntyp
! IF( na_inp( is ) < 1 ) THEN
@ -603,95 +539,6 @@ CONTAINS
RETURN
!
CONTAINS
!
!-------------------------------------------------------------------
SUBROUTINE path_read_images( image )
!-------------------------------------------------------------------
!
IMPLICIT NONE
!
INTEGER, INTENT(in) :: image
!
!
DO ia = 1, nat
!
idx = 3 * ( ia - 1 )
!
CALL read_line( input_line, end_of_file = tend )
!
IF ( tend ) &
CALL errore( 'read_cards', &
'end of file reading atomic positions', ia )
!
CALL field_count( nfield, input_line )
!
IF ( nfield == 4 ) THEN
!
READ( input_line, * ) lb_pos, pos((idx+1),image), &
pos((idx+2),image), &
pos((idx+3),image)
!
ELSEIF ( nfield == 7 ) THEN
!
IF ( image /= 1 ) THEN
!
CALL errore( 'read_cards', &
& 'wrong number of columns in ' // &
& 'ATOMIC_POSITIONS', sp_pos(ia) )
!
ENDIF
!
READ( input_line, * ) lb_pos, pos((idx+1),image), &
pos((idx+2),image), &
pos((idx+3),image), &
if_pos(1,ia), &
if_pos(2,ia), &
if_pos(3,ia)
!
ELSE
!
CALL errore( 'read_cards', &
& 'wrong number of columns in ' // &
& 'ATOMIC_POSITIONS', sp_pos(ia) )
!
ENDIF
!
IF ( image == 1 ) THEN
!
lb_pos = adjustl( lb_pos )
!
match_label_path: DO is = 1, ntyp
!
IF ( trim( lb_pos ) == trim( atom_label(is) ) ) THEN
!
sp_pos(ia) = is
!
exit match_label_path
!
ENDIF
!
ENDDO match_label_path
!
IF ( ( sp_pos(ia) < 1 ) .or. ( sp_pos(ia) > ntyp ) ) THEN
!
CALL errore( 'read_cards', &
'wrong index in ATOMIC_POSITIONS', ia )
!
ENDIF
!
is = sp_pos(ia)
!
na_inp( is ) = na_inp( is ) + 1
!
ENDIF
!
ENDDO
!
RETURN
!
END SUBROUTINE path_read_images
!
END SUBROUTINE card_atomic_positions
!
!------------------------------------------------------------------------
@ -1660,255 +1507,6 @@ CONTAINS
!
END SUBROUTINE card_constraints
!
SUBROUTINE card_collective_vars( input_line )
!
IMPLICIT NONE
!
CHARACTER(len=256) :: input_line
INTEGER :: i, nfield
LOGICAL :: ltest
LOGICAL, SAVE :: tread = .false.
!
!
IF ( tread ) CALL errore( 'card_collective_vars', 'two occurrences', 2 )
!
CALL read_line( input_line )
!
CALL field_count( nfield, input_line )
!
IF ( nfield == 1 ) THEN
!
READ( input_line, * ) ncolvar_inp
!
ELSEIF ( nfield == 2 ) THEN
!
READ( input_line, * ) ncolvar_inp, colvar_tol_inp
!
ELSE
!
CALL errore( 'card_collective_vars', 'too many fields', nfield )
!
ENDIF
!
CALL allocate_input_colvar()
!
IF ( cg_phs_path_flag ) THEN
!
input_images = 2
!
IF( allocated( pos ) ) DEALLOCATE( pos )
!
ALLOCATE( pos( ncolvar_inp, input_images ) )
!
pos(:,:) = 0.0_DP
!
ENDIF
!
DO i = 1, ncolvar_inp
!
CALL read_line( input_line )
!
READ( input_line, * ) colvar_type_inp(i)
!
CALL field_count( nfield, input_line )
!
ltest = ( ( nfield <= nc_fields + 2 ) .or. &
( cg_phs_path_flag .and. ( nfield <= nc_fields + 4 ) ) )
!
IF ( .not. ltest ) &
CALL errore( 'card_collective_vars', 'too many fields for ' // &
& 'this constraint: ' // trim( constr_type_inp(i) ), i )
!
SELECT CASE( colvar_type_inp(i) )
CASE( 'type_coord', 'atom_coord' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
colvar_inp(4,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 5 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
colvar_inp(4,i)
!
ELSE
!
CALL errore( 'card_collective_vars', 'type_coord, ' // &
& 'atom_coord: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'distance' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 3 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'distance: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'planar_angle' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 4 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'planar_angle: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'torsional_angle' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
colvar_inp(4,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 5 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
colvar_inp(4,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'torsional_angle: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'struct_fac' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 4 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
colvar_inp(2,i), &
colvar_inp(3,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'struct_fac: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'sph_struct_fac' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 2 ) THEN
!
READ( input_line, * ) colvar_type_inp(i), &
colvar_inp(1,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'sph_struct_fac: wrong number of fields', nfield )
!
ENDIF
!
CASE( 'bennett_proj' )
!
IF ( cg_phs_path_flag ) THEN
!
READ( input_line, * ) constr_type_inp(i), &
constr_inp(1,i), &
constr_inp(2,i), &
constr_inp(3,i), &
constr_inp(4,i), &
pos(i,1), &
pos(i,2)
!
ELSEIF ( nfield == 5 ) THEN
!
READ( input_line, * ) constr_type_inp(i), &
constr_inp(1,i), &
constr_inp(2,i), &
constr_inp(3,i), &
constr_inp(4,i)
!
ELSE
!
CALL errore( 'card_collective_vars', &
& 'bennett_proj: wrong number of fields', nfield )
!
ENDIF
!
CASE DEFAULT
!
CALL errore( 'card_collective_vars', 'unknown collective ' // &
& 'variable: ' // trim( colvar_type_inp(i) ), 1 )
!
END SELECT
!
ENDDO
!
tread = .true.
!
RETURN
!
END SUBROUTINE card_collective_vars
!
!------------------------------------------------------------------------
! BEGIN manual
@ -2017,71 +1615,6 @@ CONTAINS
!
!
!
!------------------------------------------------------------------------
! BEGIN manual
!----------------------------------------------------------------------
!
! CLIMBING_IMAGES
!
! Needed to explicitly specify which images have to climb
!
! Syntax:
!
! CLIMBING_IMAGES
! index1, ..., indexN
!
! Where:
!
! index1, ..., indexN are indices of the images that have to climb
!
!----------------------------------------------------------------------
! END manual
!------------------------------------------------------------------------
!
SUBROUTINE card_climbing_images( input_line )
!
IMPLICIT NONE
!
CHARACTER(len=256) :: input_line
LOGICAL, SAVE :: tread = .false.
LOGICAL, EXTERNAL :: matches
!
INTEGER :: i
CHARACTER(len=5) :: i_char
!
CHARACTER(len=6), EXTERNAL :: int_to_char
!
!
IF ( tread ) &
CALL errore( ' card_climbing_images ', ' two occurrences', 2 )
!
IF ( CI_scheme == 'manual' ) THEN
!
IF ( allocated( climbing ) ) DEALLOCATE( climbing )
!
ALLOCATE( climbing( num_of_images ) )
!
climbing(:) = .false.
!
CALL read_line( input_line )
!
DO i = 1, num_of_images
!
i_char = int_to_char( i )
!
IF ( matches( ' ' // trim( i_char ) // ',' , &
' ' // trim( input_line ) // ',' ) ) &
climbing(i) = .true.
!
ENDDO
!
ENDIF
!
tread = .true.
!
RETURN
!
END SUBROUTINE card_climbing_images
!
!------------------------------------------------------------------------
! BEGIN manual

View File

@ -34,8 +34,7 @@ MODULE read_namelists_module
system_bcast, ee_bcast, electrons_bcast, ions_bcast, cell_bcast, &
press_ai_bcast, wannier_bcast, wannier_ac_bcast, control_checkin, &
system_checkin, electrons_checkin, ions_checkin, cell_checkin, &
wannier_checkin, wannier_ac_checkin, fixval, &
path_read_namelist, path_defaults, path_checkin, path_bcast
wannier_checkin, wannier_ac_checkin, fixval
!
! ... end of module-scope declarations
!
@ -521,44 +520,6 @@ MODULE read_namelists_module
!
END SUBROUTINE
!
!=----------------------------------------------------------------------=!
!
! Variables initialization for Namelist PATH
!
!=----------------------------------------------------------------------=!
!
!-----------------------------------------------------------------------
SUBROUTINE path_defaults( )
!-----------------------------------------------------------------------
!
IMPLICIT NONE
!
!
! ... ( 'full' | 'coarse-grained' )
!
! ... defaults for "path" optimisations variables
!
string_method = 'neb'
num_of_images = 0
first_last_opt = .FALSE.
use_masses = .FALSE.
use_freezing = .FALSE.
opt_scheme = 'quick-min'
temp_req = 0.0_DP
ds = 1.0_DP
path_thr = 0.05_DP
CI_scheme = 'no-CI'
k_max = 0.1_DP
k_min = 0.1_DP
fixed_tan = .FALSE.
nstep_path = 1
restart_mode = 'from_scratch'
!
! for reading ions namelist we need to set calculation=relax
!
RETURN
!
END SUBROUTINE
!
!=----------------------------------------------------------------------=!
!
@ -1079,42 +1040,6 @@ MODULE read_namelists_module
!
END SUBROUTINE
!
!=----------------------------------------------------------------------=!
!
! Broadcast variables values for Namelist NEB
!
!=----------------------------------------------------------------------=!
!
!-----------------------------------------------------------------------
SUBROUTINE path_bcast()
!-----------------------------------------------------------------------
!
USE io_global, ONLY: ionode_id
USE mp, ONLY: mp_bcast
!
IMPLICIT NONE
!
! ... "path" variables broadcast
!
CALL mp_bcast ( string_method, ionode_id )
CALL mp_bcast( num_of_images, ionode_id )
CALL mp_bcast( first_last_opt, ionode_id )
CALL mp_bcast( use_masses, ionode_id )
CALL mp_bcast( use_freezing, ionode_id )
CALL mp_bcast( fixed_tan, ionode_id )
CALL mp_bcast( CI_scheme, ionode_id )
CALL mp_bcast( opt_scheme, ionode_id )
CALL mp_bcast( temp_req, ionode_id )
CALL mp_bcast( ds, ionode_id )
CALL mp_bcast( k_max, ionode_id )
CALL mp_bcast( k_min, ionode_id )
CALL mp_bcast( path_thr, ionode_id )
CALL mp_bcast( nstep_path, ionode_id )
CALL mp_bcast( restart_mode, ionode_id )
!
RETURN
!
END SUBROUTINE
!
!=----------------------------------------------------------------------=!
!
@ -1583,54 +1508,6 @@ MODULE read_namelists_module
!
!=----------------------------------------------------------------------=!
!
!-----------------------------------------------------------------------
SUBROUTINE path_checkin( )
!-----------------------------------------------------------------------
!
IMPLICIT NONE
!
CHARACTER(LEN=20) :: sub_name = ' path_checkin '
INTEGER :: i
LOGICAL :: allowed = .FALSE.
!
!
! ... general "path" variables checkin
IF ( ds < 0.0_DP ) &
CALL errore( sub_name,' ds out of range ',1)
IF ( temp_req < 0.0_DP ) &
CALL errore( sub_name,' temp_req out of range ',1)
!
allowed = .FALSE.
DO i = 1, SIZE( opt_scheme_allowed )
IF ( TRIM( opt_scheme ) == &
opt_scheme_allowed(i) ) allowed = .TRUE.
END DO
IF ( .NOT. allowed ) &
CALL errore( sub_name, ' opt_scheme '''// &
& TRIM( opt_scheme )//''' not allowed ', 1 )
!
!
! ... NEB(SM) specific checkin
!
IF ( k_max < 0.0_DP ) CALL errore( sub_name, 'k_max out of range', 1 )
IF ( k_min < 0.0_DP ) CALL errore( sub_name, 'k_min out of range', 1 )
IF ( k_max < k_min ) CALL errore( sub_name, 'k_max < k_min', 1 )
!
! IF ( nstep_path < 1 ) CALL errore ( sub_name, 'step_path out of range', 1 )
!
allowed = .FALSE.
DO i = 1, SIZE( CI_scheme_allowed )
IF ( TRIM( CI_scheme ) == CI_scheme_allowed(i) ) allowed = .TRUE.
END DO
!
IF ( .NOT. allowed ) &
CALL errore( sub_name, ' CI_scheme ''' // &
& TRIM( CI_scheme ) //''' not allowed ', 1 )
!
RETURN
!
END SUBROUTINE
!
!=----------------------------------------------------------------------=!
!
!-----------------------------------------------------------------------
@ -1786,27 +1663,27 @@ MODULE read_namelists_module
ELSE IF( prog == 'PW' ) THEN
ion_dynamics = 'beeman'
END IF
CASE ( 'neb' )
! CASE ( 'neb' )
!
! ... "path" optimizations
!
IF( prog == 'CP' ) THEN
! IF( prog == 'CP' ) THEN
!
electron_dynamics = 'damp'
ion_dynamics = 'none'
cell_dynamics = 'none'
! electron_dynamics = 'damp'
! ion_dynamics = 'none'
! cell_dynamics = 'none'
!
END IF
! END IF
!
CASE ( 'smd' )
!
IF( prog == 'CP' ) THEN
!
electron_dynamics = 'damp'
ion_dynamics = 'damp'
!
END IF
! CASE ( 'smd' )
!
! IF( prog == 'CP' ) THEN
! !
! electron_dynamics = 'damp'
! ion_dynamics = 'damp'
! !
! END IF
! !
CASE DEFAULT
!
CALL errore( sub_name,' calculation '// &
@ -1894,9 +1771,9 @@ MODULE read_namelists_module
CALL cell_defaults( prog )
CALL ee_defaults( prog )
ENDIF
IF( prog == 'SM') THEN
CALL path_defaults()
ENDIF
! IF( prog == 'SM') THEN
! CALL path_defaults()
! ENDIF
!
! ... Here start reading standard input file
!
@ -1937,7 +1814,7 @@ MODULE read_namelists_module
!
CALL system_checkin( prog )
!
CALL allocate_input_ions( ntyp, nat )
! CALL allocate_input_ions( ntyp, nat )
!
! ... ELECTRONS namelist
!
@ -2061,70 +1938,13 @@ MODULE read_namelists_module
!
ENDIF
!
IF (prog == 'SM') THEN
CALL path_read_namelist(5)
ENDIF
! IF (prog == 'SM') THEN
! CALL path_read_namelist(5)
! ENDIF
!
RETURN
!
END SUBROUTINE read_namelists
!
!
!-----------------------------------------------------------------------
SUBROUTINE path_read_namelist(unit)
!-----------------------------------------------------------------------
!
! this routine reads data from standard input and puts them into
! module-scope variables (accessible from other routines by including
! this module, or the one that contains them)
! ----------------------------------------------
!
! ... declare modules
!
USE io_global, ONLY : ionode, ionode_id
USE mp, ONLY : mp_bcast
!
IMPLICIT NONE
!
! ... declare variables
!
INTEGER, intent(in) :: unit
!
!
! ... declare other variables
!
INTEGER :: ios
!
! ... end of declarations
!
! ----------------------------------------------
!
!
! ... default settings for all namelists
!
CALL path_defaults( )
!
! ... Here start reading standard input file
!
! ... PATH namelist
!
ios = 0
IF ( ionode ) THEN
!
READ( unit, path, iostat = ios )
!
END IF
CALL mp_bcast( ios, ionode_id )
IF( ios /= 0 ) THEN
CALL errore( ' path_read_namelists ', &
& ' reading namelist path ', ABS(ios) )
END IF
!
CALL path_bcast( )
CALL path_checkin( )
!
RETURN
!
END SUBROUTINE path_read_namelist
!
END MODULE read_namelists_module

View File

@ -226,12 +226,12 @@ CONTAINS
CASE ( 'ATOMIC_LIST' )
CALL mp_bcast( atomic_positions, ionode_id )
CALL mp_bcast( nat, ionode_id )
CALL mp_bcast( num_of_images, ionode_id )
! CALL mp_bcast( num_of_images, ionode_id )
! ... ionode has already done it inside card_xml_atomic_list
IF (.not.ionode) THEN
CALL allocate_input_ions( ntyp, nat )
END IF
CALL mp_bcast( pos, ionode_id )
! CALL mp_bcast( pos, ionode_id )
CALL mp_bcast( if_pos, ionode_id )
CALL mp_bcast( na_inp, ionode_id )
CALL mp_bcast( sp_pos, ionode_id )
@ -240,24 +240,24 @@ CONTAINS
CALL mp_bcast( rd_vel, ionode_id )
CALL mp_bcast( tapos, ionode_id )
!
CASE ( 'CHAIN' )
CALL mp_bcast( atomic_positions, ionode_id )
CALL mp_bcast( nat, ionode_id )
CALL mp_bcast( num_of_images, ionode_id )
! ... ionode has already done it inside card_xml_atomic_list
IF (.not.ionode) THEN
CALL allocate_input_ions( ntyp, nat )
IF (num_of_images>1) THEN
IF ( allocated( pos ) ) deallocate( pos )
allocate( pos( 3*nat, num_of_images ) )
END IF
END IF
CALL mp_bcast( pos, ionode_id )
CALL mp_bcast( if_pos, ionode_id )
CALL mp_bcast( sp_pos, ionode_id )
! CASE ( 'CHAIN' )
! CALL mp_bcast( atomic_positions, ionode_id )
! CALL mp_bcast( nat, ionode_id )
! CALL mp_bcast( num_of_images, ionode_id )
! ! ... ionode has already done it inside card_xml_atomic_list
! IF (.not.ionode) THEN
! CALL allocate_input_ions( ntyp, nat )
! IF (num_of_images>1) THEN
! IF ( allocated( pos ) ) deallocate( pos )
! allocate( pos( 3*nat, num_of_images ) )
! END IF
! END IF
! CALL mp_bcast( pos, ionode_id )
! CALL mp_bcast( if_pos, ionode_id )
! CALL mp_bcast( sp_pos, ionode_id )
! CALL mp_bcast( rd_pos, ionode_id )
CALL mp_bcast( na_inp, ionode_id )
CALL mp_bcast( tapos, ionode_id )
! CALL mp_bcast( na_inp, ionode_id )
! CALL mp_bcast( tapos, ionode_id )
!
CASE ( 'CONSTRAINTS' )
CALL mp_bcast( nconstr_inp, ionode_id )
@ -288,9 +288,9 @@ CONTAINS
END IF
CALL mp_bcast( f_inp, ionode_id )
!
CASE ( 'CLIMBING_IMAGES' )
IF ( .not.ionode ) ALLOCATE( climbing( num_of_images ) )
CALL mp_bcast( climbing, ionode_id )
! CASE ( 'CLIMBING_IMAGES' )
! IF ( .not.ionode ) ALLOCATE( climbing( num_of_images ) )
! CALL mp_bcast( climbing, ionode_id )
!
CASE ( 'PLOT_WANNIER' )
CALL mp_bcast( wannier_index, ionode_id )
@ -971,165 +971,165 @@ CONTAINS
!
end_of_chain = .false.
CALL iotk_scan_begin( xmlinputunit, 'chain', attr, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
&of chain node', abs(ierr) )
! CALL iotk_scan_begin( xmlinputunit, 'chain', attr, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
! &of chain node', abs(ierr) )
! !
! !
! CALL iotk_scan_attr( attr, 'num_of_images', num_of_images, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading &
! &num_of_images attribute of chain node', abs(ierr) )
! !
! IF ( num_of_images < 1 ) CALL errore ( 'card_xml_chain', 'null &
! &or negative num_of_images', 1 )
! !
! CALL find_image( 1 )
! IF (end_of_chain) CALL errore( 'card_xml_chain', 'first image not found', 1 )
! !
! CALL iotk_scan_attr( attr, 'units', atomic_positions, found = found, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading units attribute &
! &of atomic_list node', abs(ierr) )
! !
! IF ( found ) THEN
! IF ( (trim( atomic_positions ) == 'crystal') .or. &
! (trim( atomic_positions ) == 'bohr') .or. &
! (trim( atomic_positions ) == 'angstrom').or. &
! (trim( atomic_positions ) == 'alat') ) THEN
! atomic_positions = trim( atomic_positions )
! ELSE
! CALL errore( 'car_xml_chain', &
! 'error in units attribute of atomic_list node, unknow '&
! & //trim(atomic_positions)//' units', 1 )
! ENDIF
! ELSE
! ! ... default value
! atomic_positions = 'alat'
! ENDIF
! !
! CALL iotk_scan_attr( attr, 'nat', nat, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading nat attribute &
! &of atomic_list node', abs(ierr) )
! !
! IF ( nat < 1 ) THEN
! CALL errore( 'card_xml_chain', 'nat out of range', abs(nat) )
! END IF
!
! ! ... allocation of needed arrays
! CALL allocate_input_ions( ntyp, nat )
! !
! if_pos = 1
! sp_pos = 0
! rd_pos = 0.0_DP
! na_inp = 0
! !
! !
! IF ( allocated( pos ) ) deallocate( pos )
! allocate( pos( 3*nat, num_of_images ) )
!
! allocate( tmp_image( 3, nat ) )
!
CALL iotk_scan_attr( attr, 'num_of_images', num_of_images, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading &
&num_of_images attribute of chain node', abs(ierr) )
! pos(:, :) = 0.0_DP
!
IF ( num_of_images < 1 ) CALL errore ( 'card_xml_chain', 'null &
&or negative num_of_images', 1 )
! CALL read_image( 1, tmp_image )
! ! ... transfer of tmp_image data in pos array (to mantain compatibility)
! CALL reshaffle_indexes( 1 )
!
CALL find_image( 1 )
IF (end_of_chain) CALL errore( 'card_xml_chain', 'first image not found', 1 )
! input_images = 1
!
CALL iotk_scan_attr( attr, 'units', atomic_positions, found = found, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading units attribute &
&of atomic_list node', abs(ierr) )
! DO
! !
! ! ... a trick to move the cursor at the beginning of chain node
! !
! CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of &
! &atomic_list node', input_images )
! !
! CALL iotk_scan_end( xmlinputunit, 'chain', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of chain &
! &node', abs(ierr) )
! !
! CALL iotk_scan_begin( xmlinputunit, 'chain', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
! &of chain node', abs( ierr ) )
! ! ... end of the trick
! !
! CALL find_image( input_images + 1 )
! !
! IF (end_of_chain) EXIT
! !
! input_images = input_images + 1
! !
! IF ( input_images > num_of_images ) CALL errore( 'card_xml_chain',&
! 'too many images in chain node', 1 )
! !
! CALL read_image( input_images, tmp_image )
! ! ... transfer tmp_image data in pos array (to mantain compatibility)
! CALL reshaffle_indexes( input_images )
! !
! ENDDO
! !
! CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of &
! &atomic_list node', abs(ierr) )
! !
! !
! tapos = .true.
!
IF ( found ) THEN
IF ( (trim( atomic_positions ) == 'crystal') .or. &
(trim( atomic_positions ) == 'bohr') .or. &
(trim( atomic_positions ) == 'angstrom').or. &
(trim( atomic_positions ) == 'alat') ) THEN
atomic_positions = trim( atomic_positions )
ELSE
CALL errore( 'car_xml_chain', &
'error in units attribute of atomic_list node, unknow '&
& //trim(atomic_positions)//' units', 1 )
ENDIF
ELSE
! ... default value
atomic_positions = 'alat'
ENDIF
!
CALL iotk_scan_attr( attr, 'nat', nat, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading nat attribute &
&of atomic_list node', abs(ierr) )
!
IF ( nat < 1 ) THEN
CALL errore( 'card_xml_chain', 'nat out of range', abs(nat) )
END IF
! ... allocation of needed arrays
CALL allocate_input_ions( ntyp, nat )
!
if_pos = 1
sp_pos = 0
rd_pos = 0.0_DP
na_inp = 0
!
!
IF ( allocated( pos ) ) deallocate( pos )
allocate( pos( 3*nat, num_of_images ) )
!
allocate( tmp_image( 3, nat ) )
!
pos(:, :) = 0.0_DP
!
CALL read_image( 1, tmp_image )
! ... transfer of tmp_image data in pos array (to mantain compatibility)
CALL reshaffle_indexes( 1 )
!
input_images = 1
!
DO
!
! ... a trick to move the cursor at the beginning of chain node
!
CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of &
&atomic_list node', input_images )
!
CALL iotk_scan_end( xmlinputunit, 'chain', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of chain &
&node', abs(ierr) )
!
CALL iotk_scan_begin( xmlinputunit, 'chain', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
&of chain node', abs( ierr ) )
! ... end of the trick
!
CALL find_image( input_images + 1 )
!
IF (end_of_chain) EXIT
!
input_images = input_images + 1
!
IF ( input_images > num_of_images ) CALL errore( 'card_xml_chain',&
'too many images in chain node', 1 )
!
CALL read_image( input_images, tmp_image )
! ... transfer tmp_image data in pos array (to mantain compatibility)
CALL reshaffle_indexes( input_images )
!
ENDDO
!
CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end of &
&atomic_list node', abs(ierr) )
!
!
tapos = .true.
!
DEALLOCATE(tmp_image)
! DEALLOCATE(tmp_image)
RETURN
!
CONTAINS
! CONTAINS
!
! ... does a scan to find the image with attribute num="iimage"
SUBROUTINE find_image( iimage )
!
INTEGER, INTENT( in ) :: iimage
INTEGER :: direction, rii
!
DO
CALL iotk_scan_begin( xmlinputunit, 'atomic_list', attr, &
direction = direction, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
&of atomic_list node', abs(ierr) )
!
CALL iotk_scan_attr( attr, 'num', rii, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading num &
&attribute of atomic_list node', abs(ierr) )
!
IF ( rii == iimage ) EXIT
!
IF ( direction == -1 ) THEN
end_of_chain = .true.
EXIT
END IF
!
CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end &
&of atomic_list node', abs(iimage) )
!
END DO
!
END SUBROUTINE find_image
!
! ... copy the data from tmp_image to pos, necessary to mantain the notation
! ... of old input
SUBROUTINE reshaffle_indexes( iimage )
!
INTEGER, INTENT( in ) :: iimage
INTEGER :: ia_tmp, idx_tmp
DO ia_tmp = 1,nat
idx_tmp = 3*(ia_tmp -1 )
pos(idx_tmp+1:idx_tmp+3, iimage) = tmp_image( 1:3, ia_tmp )
END DO
END SUBROUTINE reshaffle_indexes
!
! SUBROUTINE find_image( iimage )
! !
! INTEGER, INTENT( in ) :: iimage
! INTEGER :: direction, rii
! !
! DO
! CALL iotk_scan_begin( xmlinputunit, 'atomic_list', attr, &
! direction = direction, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning begin &
! &of atomic_list node', abs(ierr) )
! !
! CALL iotk_scan_attr( attr, 'num', rii, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error reading num &
! &attribute of atomic_list node', abs(ierr) )
! !
! IF ( rii == iimage ) EXIT
! !
! IF ( direction == -1 ) THEN
! end_of_chain = .true.
! EXIT
! END IF
! !
! CALL iotk_scan_end( xmlinputunit, 'atomic_list', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_chain', 'error scanning end &
! &of atomic_list node', abs(iimage) )
! !
! END DO
! !
! END SUBROUTINE find_image
! !
! ! ... copy the data from tmp_image to pos, necessary to mantain the notation
! ! ... of old input
! SUBROUTINE reshaffle_indexes( iimage )
! !
! INTEGER, INTENT( in ) :: iimage
! INTEGER :: ia_tmp, idx_tmp
!
! DO ia_tmp = 1,nat
! idx_tmp = 3*(ia_tmp -1 )
! pos(idx_tmp+1:idx_tmp+3, iimage) = tmp_image( 1:3, ia_tmp )
! END DO
! END SUBROUTINE reshaffle_indexes
! !
END SUBROUTINE card_xml_chain
!
!
!
! ... Subroutine that reads a single image inside chain node
!
! ! ... Subroutine that reads a single image inside chain node
! !
SUBROUTINE read_image( image, image_pos, image_vel )
!
IMPLICIT NONE
@ -1248,14 +1248,14 @@ CONTAINS
IF ( ierr /= 0 ) CALL errore( 'read_image', 'error scanning end of &
&atom node', abs(ierr) )
!
! IF ( image == 1) THEN
! DO is = 1, ntyp
! IF( na_inp( is ) < 1 ) &
! CALL errore( 'read_image', 'no atom found in atomic_list for '&
! //trim(atom_label(is))//' specie', is )
! ENDDO
! ENDIF
!
IF ( image == 1) THEN
DO is = 1, ntyp
IF( na_inp( is ) < 1 ) &
CALL errore( 'read_image', 'no atom found in atomic_list for '&
//trim(atom_label(is))//' specie', is )
ENDDO
ENDIF
!
RETURN
!
END SUBROUTINE read_image
@ -1823,63 +1823,63 @@ CONTAINS
!_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_-_!
!
SUBROUTINE card_xml_climbing_images( )
!
IMPLICIT NONE
!
!
INTEGER :: i, num_climb_images, ierr
INTEGER, DIMENSION(:), ALLOCATABLE :: tmp
CHARACTER (LEN=iotk_attlenx) :: attr
!
!
IF ( CI_scheme == 'manual' ) THEN
!
IF ( allocated( climbing ) ) deallocate( climbing )
!
allocate( climbing( num_of_images ) )
!
climbing( : ) = .FALSE.
!
CALL iotk_scan_begin( xmlinputunit, 'images', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning begin of &
&images node', abs( ierr ) )
!
CALL iotk_scan_begin( xmlinputunit, 'integer', attr, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning begin of &
&integer node', abs( ierr ) )
!
CALL iotk_scan_end( xmlinputunit, 'integer', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning end of &
&integer node', abs( ierr ) )
!
CALL iotk_scan_attr( attr, 'n1', num_climb_images, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error reading n1 attribute of &
&integer node', abs( ierr ) )
!
IF ( num_climb_images < 1 ) CALL errore( 'card_xml_climbing_images', 'non positive value &
&of num_climb_images', abs( num_climb_images ) )
!
allocate( tmp( num_climb_images ) )
!
CALL iotk_scan_dat_inside( xmlinputunit, tmp, ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error reading data inside &
&images node', abs( ierr ) )
!
CALL iotk_scan_end( xmlinputunit, 'images', ierr = ierr )
IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning end of &
&images node', abs( ierr ) )
!
DO i = 1, num_climb_images
!
IF ( ( tmp(i) > num_of_images ) .or. ( tmp(i)<0 ) ) CALL errore('card_xml_climbing_images',&
"image that doesn't exist", 1 )
!
climbing(tmp(i)) = .true.
!
ENDDO
!
ENDIF
!
! !
! IMPLICIT NONE
! !
! !
! INTEGER :: i, num_climb_images, ierr
! INTEGER, DIMENSION(:), ALLOCATABLE :: tmp
! CHARACTER (LEN=iotk_attlenx) :: attr
! !
! !
! IF ( CI_scheme == 'manual' ) THEN
! !
! IF ( allocated( climbing ) ) deallocate( climbing )
! !
! allocate( climbing( num_of_images ) )
! !
! climbing( : ) = .FALSE.
! !
! CALL iotk_scan_begin( xmlinputunit, 'images', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning begin of &
! &images node', abs( ierr ) )
! !
! CALL iotk_scan_begin( xmlinputunit, 'integer', attr, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning begin of &
! &integer node', abs( ierr ) )
! !
! CALL iotk_scan_end( xmlinputunit, 'integer', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning end of &
! &integer node', abs( ierr ) )
! !
! CALL iotk_scan_attr( attr, 'n1', num_climb_images, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error reading n1 attribute of &
! &integer node', abs( ierr ) )
! !
! IF ( num_climb_images < 1 ) CALL errore( 'card_xml_climbing_images', 'non positive value &
! &of num_climb_images', abs( num_climb_images ) )
! !
! allocate( tmp( num_climb_images ) )
! !
! CALL iotk_scan_dat_inside( xmlinputunit, tmp, ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error reading data inside &
! &images node', abs( ierr ) )
! !
! CALL iotk_scan_end( xmlinputunit, 'images', ierr = ierr )
! IF ( ierr /= 0 ) CALL errore( 'card_xml_climbing_images', 'error scanning end of &
! &images node', abs( ierr ) )
! !
! DO i = 1, num_climb_images
! !
! IF ( ( tmp(i) > num_of_images ) .or. ( tmp(i)<0 ) ) CALL errore('card_xml_climbing_images',&
! "image that doesn't exist", 1 )
! !
! climbing(tmp(i)) = .true.
! !
! ENDDO
! !
! ENDIF
! !
RETURN
!
!

View File

@ -9,7 +9,7 @@ MODULE read_xml_fields_module
!
USE io_global, ONLY : xmlinputunit
USE kinds, ONLY : DP
USE input_parameters
USE input_parameters
!
!
IMPLICIT NONE
@ -219,9 +219,9 @@ CONTAINS
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
cell_velocities = clean_str(tmpstr)
!
CASE ( 'CI_scheme' )
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
CI_scheme = clean_str(tmpstr)
! CASE ( 'CI_scheme' )
! CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
! CI_scheme = clean_str(tmpstr)
!
CASE ( 'comp_thr' )
CALL iotk_scan_dat_inside( xmlinputunit, comp_thr, ierr = ierr )
@ -273,8 +273,8 @@ CONTAINS
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
disk_io = clean_str(tmpstr)
!
CASE ( 'ds' )
CALL iotk_scan_dat_inside( xmlinputunit, ds, ierr = ierr )
! CASE ( 'ds' )
! CALL iotk_scan_dat_inside( xmlinputunit, ds, ierr = ierr )
!
CASE ( 'dthr' )
CALL iotk_scan_dat_inside( xmlinputunit, dthr, ierr = ierr )
@ -374,8 +374,8 @@ CONTAINS
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
exchange_grad_corr = clean_str(tmpstr)
!
CASE ( 'first_last_opt' )
CALL iotk_scan_dat_inside( xmlinputunit, first_last_opt, ierr = ierr )
! CASE ( 'first_last_opt' )
! CALL iotk_scan_dat_inside( xmlinputunit, first_last_opt, ierr = ierr )
!
CASE ( 'fixed_magnetization' )
CALL iotk_scan_dat_inside( xmlinputunit, fixed_magnetization, ierr = ierr )
@ -407,11 +407,11 @@ CONTAINS
CASE ( 'greasp' )
CALL iotk_scan_dat_inside( xmlinputunit, greasp, ierr = ierr )
!
CASE ( 'k_max' )
CALL iotk_scan_dat_inside( xmlinputunit, k_max, ierr = ierr )
! CASE ( 'k_max' )
! CALL iotk_scan_dat_inside( xmlinputunit, k_max, ierr = ierr )
!
CASE ( 'k_min' )
CALL iotk_scan_dat_inside( xmlinputunit, k_min, ierr = ierr )
! CASE ( 'k_min' )
! CALL iotk_scan_dat_inside( xmlinputunit, k_min, ierr = ierr )
!
CASE ( 'iprint' )
CALL iotk_scan_dat_inside( xmlinputunit, iprint, ierr = ierr )
@ -602,9 +602,9 @@ CONTAINS
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
occupations = clean_str(tmpstr)
!
CASE ( 'opt_scheme' )
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
opt_scheme = clean_str(tmpstr)
! CASE ( 'opt_scheme' )
! CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
! opt_scheme = clean_str(tmpstr)
!
CASE ( 'ortho_eps' )
CALL iotk_scan_dat_inside( xmlinputunit, ortho_eps, ierr = ierr )
@ -632,12 +632,12 @@ CONTAINS
CASE ( 'passop' )
CALL iotk_scan_dat_inside( xmlinputunit, passop, ierr = ierr )
!
CASE ( 'path_thr' )
CALL iotk_scan_dat_inside( xmlinputunit, path_thr, ierr = ierr )
! CASE ( 'path_thr' )
! CALL iotk_scan_dat_inside( xmlinputunit, path_thr, ierr = ierr )
!
CASE ( 'phase_space' )
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
phase_space = clean_str(tmpstr)
! CASE ( 'phase_space' )
! CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
! phase_space = clean_str(tmpstr)
!
CASE ( 'pot_extrapolation' )
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
@ -708,8 +708,8 @@ CONTAINS
CASE ( 'tefield' )
CALL iotk_scan_dat_inside( xmlinputunit, tefield, ierr = ierr )
!
CASE ( 'temp_req' )
CALL iotk_scan_dat_inside( xmlinputunit, temp_req, ierr = ierr )
! CASE ( 'temp_req' )
! CALL iotk_scan_dat_inside( xmlinputunit, temp_req, ierr = ierr )
!
CASE ( 'temph' )
CALL iotk_scan_dat_inside( xmlinputunit, temph, ierr = ierr )
@ -751,11 +751,11 @@ CONTAINS
CALL iotk_scan_dat_inside( xmlinputunit, tmpstr, ierr = ierr )
U_projection_type = clean_str(tmpstr)
!
CASE ( 'use_masses' )
CALL iotk_scan_dat_inside( xmlinputunit, use_masses, ierr = ierr )
! CASE ( 'use_masses' )
! CALL iotk_scan_dat_inside( xmlinputunit, use_masses, ierr = ierr )
!
CASE ( 'use_freezing' )
CALL iotk_scan_dat_inside( xmlinputunit, use_freezing, ierr = ierr )
! CASE ( 'use_freezing' )
! CALL iotk_scan_dat_inside( xmlinputunit, use_freezing, ierr = ierr )
!
CASE ( 'upscale' )
CALL iotk_scan_dat_inside( xmlinputunit, upscale, ierr = ierr )