init_input_unit Subroutine

public subroutine init_input_unit(open_it)

Opens the input file, strip out any comments and write them into the file .<run_name>.in. Check for includes, read any lines from the includes, strip any comments from them and add them to the same file.

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: open_it

If true, open the file, otherwise do nothing


Contents

Source Code


Source Code

  subroutine init_input_unit (open_it)
    implicit none
    !> If true, open the file, otherwise do nothing
    logical, intent (in) :: open_it
    integer :: in_unit, out_unit, iostat
    character(500) :: line
    integer :: ind_slash    !To hold position of slash in run_name
    ! for includes
    integer, parameter :: stack_size = 10
    integer, dimension (stack_size) :: stack
    integer :: stack_ptr
    logical :: already_opened
    character(len=75) :: non_end_error_message

    if (.not. open_it) then
       input_unit_no = -1
       return
    end if

    stack_ptr = 0

    call get_unused_unit (in_unit)
    open (unit=in_unit, file=trim(run_name)//".in", status="old", &
         action="read", iostat=iostat)
    if (iostat /= 0) then
       call close_stack_and_abort("Couldn't open input file: " // trim(run_name) // ".in")
    end if

    call get_unused_unit (out_unit)
    !Determine if '/' is in input name and if so what position
    !in the string is the last one (i.e. split run_name into path_to_file and file)
    ind_slash=index(run_name,"/",.True.)
    if (ind_slash.EQ.0) then !No slash in name
        !Original behaviour
        open (unit=out_unit, file="."//trim(run_name)//".in")
    else
        !General behaviour
        open (unit=out_unit, file=trim(run_name(1:ind_slash))//"."//trim(run_name(ind_slash+1:))//".in")
    endif

    iostat = 0
    num_input_lines = 0
    do
       read (unit=in_unit, fmt="(a)", iostat=iostat) line

       ! It appears that we're using iostat / =0 to identify when
       ! we've reached the end of the current file. This therefore
       ! ignores any other possible errors. We should perhaps instead
       ! first check if iostat_is_end(iostat), if so proceed as we
       ! have here else if iostat /= 0 we have some other error and
       ! should consider aborting. Currently we just display an error
       ! message but carry on as usual.
       if (iostat /= 0) then
          if (.not. is_iostat_end(iostat)) then
             write(non_end_error_message, '(A, I0)') "Error encountered whilst reading input file with code ", iostat
             call close_stack_and_abort(non_end_error_message)
          end if
          if (stack_ptr <= 0) exit
          close (unit=in_unit)
          iostat = 0
          in_unit = stack(stack_ptr)
          stack_ptr = stack_ptr - 1
          cycle
       end if

       if (line(1:9) == "!include ") then
          if (stack_ptr >= stack_size) then
             call close_stack_and_abort("!include ignored: nesting too deep: " // trim(line))
          end if
          stack_ptr = stack_ptr + 1
          stack(stack_ptr) = in_unit

          call get_unused_unit (in_unit)

          ! Check if we've already opened this file, if so assume this
          ! is a circular dependency and abort
          inquire(file = trim(line(10:)), opened = already_opened)
          if (already_opened) then
             call close_stack_and_abort("Circular dependency with " // trim(line))
          end if

          open (unit=in_unit, file=trim(line(10:)), status="old", &
               action="read", iostat=iostat)

          ! Here we assume that any problem with the above open is due
          ! to the file being "unreadable". This could also end up
          ! catching circular dependencies in our includes as the
          ! fortran standard forbids having the same file open with
          ! different file units (although some compilers may allow
          ! this as an extension). To help the user we first detect if
          ! this file has already been opened and if so warn for
          ! circular dependency. Here we therefore deal with all other
          ! errors.
          if (iostat /= 0) then
             call close_stack_and_abort("!include ignored: file unreadable: " // trim(line))
          end if
          cycle
       end if
       call strip_comments (line)
       call replace_leading_tabs(line)
       write (unit=out_unit, fmt="(a)") trim(line)
       num_input_lines = num_input_lines + 1
    end do
    close (unit=in_unit)

    input_unit_no = out_unit
  contains
    !> Close all open files and abort run
    subroutine close_stack_and_abort(error_message)
      use mp, only : mp_abort
      !> Error message to print to screen and log in error file
      character(len=*), intent(in) :: error_message
      integer :: i
      do i = 1, stack_ptr
        close(i)
      end do
      call mp_abort(error_message, to_screen=.true.)
    end subroutine close_stack_and_abort
  end subroutine init_input_unit