param_get_keyword_block Subroutine

private subroutine param_get_keyword_block(keyword, found, rows, columns, c_value, l_value, i_value, r_value)

Uses

  • proc~~param_get_keyword_block~~UsesGraph proc~param_get_keyword_block param_get_keyword_block module~w90_constants w90_constants proc~param_get_keyword_block->module~w90_constants module~w90_io w90_io proc~param_get_keyword_block->module~w90_io module~w90_io->module~w90_constants

Finds the values of the required data block

Arguments

Type IntentOptional AttributesName
character(len=*), intent(in) :: keyword

Keyword to examine

logical, intent(out) :: found

Is keyword present

integer, intent(in) :: rows

Number of rows

integer, intent(in) :: columns

Number of columns

character(len=*), intent(inout), optional :: c_value(columns,rows)

keyword block data

logical, intent(inout), optional :: l_value(columns,rows)

keyword block data

integer, intent(inout), optional :: i_value(columns,rows)

keyword block data

real(kind=dp), intent(inout), optional :: r_value(columns,rows)

keyword block data


Calls

proc~~param_get_keyword_block~~CallsGraph proc~param_get_keyword_block param_get_keyword_block proc~io_error io_error proc~param_get_keyword_block->proc~io_error

Called by

proc~~param_get_keyword_block~~CalledByGraph proc~param_get_keyword_block param_get_keyword_block proc~param_read param_read proc~param_read->proc~param_get_keyword_block program~wannier wannier program~wannier->proc~param_read proc~wannier_run wannier_run proc~wannier_run->proc~param_read proc~wannier_setup wannier_setup proc~wannier_setup->proc~param_read program~postw90 postw90 program~postw90->proc~param_read

Contents


Source Code

  subroutine param_get_keyword_block(keyword, found, rows, columns, c_value, l_value, i_value, r_value)
    !==============================================================================================!
    !                                                                                              !
    !!   Finds the values of the required data block
    !                                                                                              !
    !==============================================================================================!

    use w90_constants, only: bohr
    use w90_io, only: io_error

    implicit none

    character(*), intent(in)  :: keyword
    !! Keyword to examine
    logical, intent(out) :: found
    !! Is keyword present
    integer, intent(in)  :: rows
    !! Number of rows
    integer, intent(in)  :: columns
    !! Number of columns
    character(*), optional, intent(inout) :: c_value(columns, rows)
    !! keyword block data
    logical, optional, intent(inout) :: l_value(columns, rows)
    !! keyword block data
    integer, optional, intent(inout) :: i_value(columns, rows)
    !! keyword block data
    real(kind=dp), optional, intent(inout) :: r_value(columns, rows)
    !! keyword block data

    integer           :: in, ins, ine, loop, i, line_e, line_s, counter, blen
    logical           :: found_e, found_s, lconvert
    character(len=maxlen) :: dummy, end_st, start_st

    found_s = .false.
    found_e = .false.

    start_st = 'begin '//trim(keyword)
    end_st = 'end '//trim(keyword)

    do loop = 1, num_lines
      ins = index(in_data(loop), trim(keyword))
      if (ins == 0) cycle
      in = index(in_data(loop), 'begin')
      if (in == 0 .or. in > 1) cycle
      line_s = loop
      if (found_s) then
        call io_error('Error: Found '//trim(start_st)//' more than once in input file')
      endif
      found_s = .true.
    end do

    if (.not. found_s) then
      found = .false.
      return
    end if

    do loop = 1, num_lines
      ine = index(in_data(loop), trim(keyword))
      if (ine == 0) cycle
      in = index(in_data(loop), 'end')
      if (in == 0 .or. in > 1) cycle
      line_e = loop
      if (found_e) then
        call io_error('Error: Found '//trim(end_st)//' more than once in input file')
      endif
      found_e = .true.
    end do

    if (.not. found_e) then
      call io_error('Error: Found '//trim(start_st)//' but no '//trim(end_st)//' in input file')
    end if

    if (line_e <= line_s) then
      call io_error('Error: '//trim(end_st)//' comes before '//trim(start_st)//' in input file')
    end if

    ! number of lines of data in block
    blen = line_e - line_s - 1

    !    if( blen /= rows) then
    !       if ( index(trim(keyword),'unit_cell_cart').ne.0 ) then
    !          if ( blen /= rows+1 ) call io_error('Error: Wrong number of lines in block '//trim(keyword))
    !       else
    !          call io_error('Error: Wrong number of lines in block '//trim(keyword))
    !       endif
    !    endif

    if ((blen .ne. rows) .and. (blen .ne. rows + 1)) &
      call io_error('Error: Wrong number of lines in block '//trim(keyword))

    if ((blen .eq. rows + 1) .and. (index(trim(keyword), 'unit_cell_cart') .eq. 0)) &
      call io_error('Error: Wrong number of lines in block '//trim(keyword))

    found = .true.

    lconvert = .false.
    if (blen == rows + 1) then
      dummy = in_data(line_s + 1)
      if (index(dummy, 'ang') .ne. 0) then
        lconvert = .false.
      elseif (index(dummy, 'bohr') .ne. 0) then
        lconvert = .true.
      else
        call io_error('Error: Units in block '//trim(keyword)//' not recognised')
      endif
      in_data(line_s) (1:maxlen) = ' '
      line_s = line_s + 1
    endif

!    r_value=1.0_dp
    counter = 0
    do loop = line_s + 1, line_e - 1
      dummy = in_data(loop)
      counter = counter + 1
      if (present(c_value)) read (dummy, *, err=240, end=240) (c_value(i, counter), i=1, columns)
      if (present(l_value)) then
        ! I don't think we need this. Maybe read into a dummy charater
        ! array and convert each element to logical
        call io_error('param_get_keyword_block unimplemented for logicals')
      endif
      if (present(i_value)) read (dummy, *, err=240, end=240) (i_value(i, counter), i=1, columns)
      if (present(r_value)) read (dummy, *, err=240, end=240) (r_value(i, counter), i=1, columns)
    end do

    if (lconvert) then
      if (present(r_value)) then
        r_value = r_value*bohr
      endif
    endif

    in_data(line_s:line_e) (1:maxlen) = ' '

    return

240 call io_error('Error: Problem reading block keyword '//trim(keyword))

  end subroutine param_get_keyword_block