Skip to content

Commit

Permalink
use consistent string length for error message variable
Browse files Browse the repository at this point in the history
also various unimportant initialisations
  • Loading branch information
Jerome Jackson committed Jan 15, 2025
1 parent ca8bf73 commit 9cbfc20
Show file tree
Hide file tree
Showing 5 changed files with 79 additions and 81 deletions.
6 changes: 4 additions & 2 deletions src/disentangle.F90
Original file line number Diff line number Diff line change
Expand Up @@ -972,6 +972,7 @@ subroutine dis_windows(dis_spheres, dis_manifold, eigval_opt, kpt_latt, recip_la

! Note: we assume that eigvals are ordered from the bottom up
imin = 0
imax = 0
do i = 1, num_bands
if (imin .eq. 0) then
if ((eigval_opt(i, nkp) .ge. dis_manifold%win_min) .and. &
Expand Down Expand Up @@ -2384,14 +2385,14 @@ subroutine dis_extract(dis_control, kmesh_info, sitesym, print_output, dis_manif

complex(kind=dp), allocatable :: camp_loc(:, :, :)
complex(kind=dp), allocatable :: u_matrix_opt_loc(:, :, :)
complex(kind=dp), allocatable :: ceamp(:, :, :)
complex(kind=dp), allocatable :: ceamp(:, :, :) ! (alloc on root rank only)
complex(kind=dp), allocatable :: camp(:, :, :)
complex(kind=dp), allocatable :: czmat_in(:, :, :)
complex(kind=dp), allocatable :: czmat_out(:, :, :)
! the z-matrices are now stored in local arrays
complex(kind=dp), allocatable :: czmat_in_loc(:, :, :)
complex(kind=dp), allocatable :: czmat_out_loc(:, :, :)
complex(kind=dp), allocatable :: cham(:, :, :)
complex(kind=dp), allocatable :: cham(:, :, :) ! (alloc on root rank only)

complex(kind=dp), allocatable :: cap(:)
complex(kind=dp), allocatable :: cwb(:, :), cww(:, :), cbw(:, :)
Expand Down Expand Up @@ -3624,6 +3625,7 @@ subroutine dis_extract_gamma(dis_control, kmesh_info, print_output, dis_manifold
'+---------------------------------------------------------------------+<-- DIS'

dis_converged = .false.
womegai = 0 ! unitialised if zero iterations sought

! ------------------
! BIG ITERATION LOOP
Expand Down
2 changes: 1 addition & 1 deletion src/error_base.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module w90_error_base
!! Codify error state with integer code and human readable string
type w90_error_type
integer :: code
character(len=256) :: message
character(len=128) :: message
#ifdef W90DEV
contains
final :: untrapped_error
Expand Down
6 changes: 2 additions & 4 deletions src/plot.F90
Original file line number Diff line number Diff line change
Expand Up @@ -415,8 +415,8 @@ subroutine plot_interpolate_bands(mp_grid, real_lattice, band_plot, kpoint_path,
logical, allocatable :: kpath_print_first_point(:)

character(len=20), allocatable :: glabel(:)
character(len=10), allocatable :: xlabel(:)
character(len=10), allocatable :: ctemp(:)
character(len=20), allocatable :: xlabel(:)
character(len=20), allocatable :: ctemp(:)

! mpi variables
integer :: my_node_id, num_nodes, size_rdist, size_ndeg
Expand Down Expand Up @@ -1923,8 +1923,6 @@ subroutine plot_wannier(wannier_plot, wvfn_read, wannier_data, print_output, u_m
end do
end do
end do
wmod = wmod/sqrt(real(wmod)**2 + aimag(wmod)**2)
wann_func(:, :, :, loop_w) = wann_func(:, :, :, loop_w)/wmod
end do
endif
endif
Expand Down
144 changes: 71 additions & 73 deletions src/readwrite.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3641,89 +3641,87 @@ subroutine w90_readwrite_get_projections(settings, num_proj, atom_data, num_wann
endif
endif

lconvert = .false.
lrandom = .false.
lpartrandom = .false.

if (allocated(settings%in_data)) then ! we are reading from the input file
do loop = 1, settings%num_lines
ins = index(settings%in_data(loop), trim(keyword))
if (ins == 0) cycle
in = index(settings%in_data(loop), 'begin')
if (in == 0 .or. in > 1) cycle
line_s = loop
if (found_s) then
call set_error_input(error, 'Error: Found '//trim(start_st)//' more than once in input file', comm)
do loop = 1, settings%num_lines
ins = index(settings%in_data(loop), trim(keyword))
if (ins == 0) cycle
in = index(settings%in_data(loop), 'begin')
if (in == 0 .or. in > 1) cycle
line_s = loop
if (found_s) then
call set_error_input(error, 'Error: Found '//trim(start_st)//' more than once in input file', comm)
return
endif
found_s = .true.
end do

do loop = 1, settings%num_lines
ine = index(settings%in_data(loop), trim(keyword))
if (ine == 0) cycle
in = index(settings%in_data(loop), 'end')
if (in == 0 .or. in > 1) cycle
line_e = loop
if (found_e) then
call set_error_input(error, &
'w90_readwrite_get_projections: Found '//trim(end_st)//' more than once in input file', comm)
return
endif
found_e = .true.
end do

if (.not. found_e) then
call set_error_input(error, 'w90_readwrite_get_projections: Found '//trim(start_st) &
//' but no '//trim(end_st)//' in input file', comm)
return
endif
found_s = .true.
end do
end if

do loop = 1, settings%num_lines
ine = index(settings%in_data(loop), trim(keyword))
if (ine == 0) cycle
in = index(settings%in_data(loop), 'end')
if (in == 0 .or. in > 1) cycle
line_e = loop
if (found_e) then
if (line_e <= line_s) then
call set_error_input(error, &
'w90_readwrite_get_projections: Found '//trim(end_st)//' more than once in input file', comm)
'w90_readwrite_get_projections: '//trim(end_st)//' comes before '//trim(start_st) &
//' in input file', comm)
return
endif
found_e = .true.
end do

if (.not. found_e) then
call set_error_input(error, 'w90_readwrite_get_projections: Found '//trim(start_st) &
//' but no '//trim(end_st)//' in input file', comm)
return
end if

if (line_e <= line_s) then
call set_error_input(error, &
'w90_readwrite_get_projections: '//trim(end_st)//' comes before '//trim(start_st) &
//' in input file', comm)
return
end if
end if

dummy = settings%in_data(line_s + 1)
lconvert = .false.
lrandom = .false.
lpartrandom = .false.
if (index(dummy, 'ang') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
elseif (index(dummy, 'bohr') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
lconvert = .true.
elseif (index(dummy, 'random') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
if (index(settings%in_data(line_s + 1), end_st) .ne. 0) then
lrandom = .true. ! all projections random
else
lpartrandom = .true. ! only some projections random
if (index(settings%in_data(line_s + 1), 'ang') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
elseif (index(settings%in_data(line_s + 1), 'bohr') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
lconvert = .true.
dummy = settings%in_data(line_s + 1)
if (index(dummy, 'ang') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
elseif (index(dummy, 'bohr') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
lconvert = .true.
elseif (index(dummy, 'random') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
if (index(settings%in_data(line_s + 1), end_st) .ne. 0) then
lrandom = .true. ! all projections random
else
lpartrandom = .true. ! only some projections random
if (index(settings%in_data(line_s + 1), 'ang') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
elseif (index(settings%in_data(line_s + 1), 'bohr') .ne. 0) then
if (.not. lcount) settings%in_data(line_s) (1:maxlen) = ' '
line_s = line_s + 1
lconvert = .true.
endif
endif
endif
endif

elseif (allocated(settings%entries)) then ! reading from setopt
lconvert = .false.
lrandom = .false.
lpartrandom = .false.
do loop = 1, settings%num_entries ! this means the first occurance of the variable in settings is used
if (settings%entries(loop)%keyword == 'projections') then
counter = counter + 1
if (settings%entries(loop)%txtdata == 'bohr') lconvert = .true.
if (settings%entries(loop)%txtdata == 'random') lrandom = .true.
endif
enddo
line_s = 0
line_e = settings%num_entries + 1
do loop = 1, settings%num_entries ! this means the first occurance of the variable in settings is used
if (settings%entries(loop)%keyword == 'projections') then
counter = counter + 1
if (settings%entries(loop)%txtdata == 'bohr') lconvert = .true.
if (settings%entries(loop)%txtdata == 'random') lrandom = .true.
endif
enddo
line_s = 0
line_e = settings%num_entries + 1
endif ! reading from input file or entries

counter = 0
Expand Down
2 changes: 1 addition & 1 deletion src/wannier90_readwrite.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1539,7 +1539,7 @@ subroutine w90_wannier90_readwrite_read_projections(settings, proj, proj_input,
! projections selection
integer :: num_select_projections
integer, allocatable :: select_projections(:)
integer :: imap, ip
integer :: imap

! Projections
call w90_readwrite_get_keyword(settings, 'auto_projections', found, error, comm, &
Expand Down

0 comments on commit 9cbfc20

Please sign in to comment.