File: inpfile.f90

package info (click to toggle)
espresso 6.7-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm, bullseye
  • size: 311,040 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,502; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (74 lines) | stat: -rw-r--r-- 2,357 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
!
! Copyright (C) 2002-2020 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 input_from_file( )
  !
  !! Check command-line arguments for -i[nput] "file name"
  !! if "file name" is present, attach input unit 5 to the specified file
  !! In parallel execution, must be called by a single processor 
  !
  USE open_close_input_file, ONLY : get_file_name
  !
  IMPLICIT NONE
  !
  INTEGER              :: stdin = 5, stderr = 6, ierr = 0
  CHARACTER(LEN = 256) :: input_file
  !
  input_file = get_file_name ( )
  !
  IF ( TRIM ( input_file ) /= ' ' ) THEN
    !
    OPEN ( UNIT = stdin, FILE = input_file, FORM = 'FORMATTED', &
           STATUS = 'OLD', IOSTAT = ierr )
    !
    ! do not call "errore" here: it may hang in parallel execution
    ! if this routine is called by a single processor
    !
    IF ( ierr > 0 ) WRITE (stderr, &
    '(" *** Fatal error: input file ",A," not found ***")' ) TRIM( input_file )
    !
  ELSE
    ierr = -1
  ENDIF
  !
END SUBROUTINE input_from_file

!----------------------------------------------------------------------------
!
SUBROUTINE get_file( input_file )
  !
  !! This subroutine reads, either from command line or from terminal,
  !! the name of a file to be opened. To be used for serial codes only.
  !! Expected syntax: "code [filename]"  (one command-line option, or none)
  !
  USE open_close_input_file, ONLY : get_file_name
  !
  IMPLICIT NONE
  !
  CHARACTER (LEN=*),INTENT(OUT)  :: input_file
  !! On output contains the path to the input file
  INTEGER :: stdin = 5, stdout = 6, stderr = 6
  LOGICAL :: exst
  !
  input_file = get_file_name ( )
  !
  IF ( TRIM ( input_file ) == ' ' ) THEN
10   WRITE(stdout,'(5x,"Input file > ")', advance="NO")
     READ (stdin,'(a)', end = 20, err=20) input_file
     IF ( TRIM(input_file) == ' ') GO TO 10
     INQUIRE ( FILE = input_file, EXIST = exst )
     IF ( .NOT. exst ) THEN
        WRITE(stderr,'(A,": file not found")') TRIM(input_file)
        GO TO 10
     END IF
  END IF
  RETURN
20 WRITE(stdout,'("Fatal error reading file name ",A)') TRIM(input_file)
  !
END SUBROUTINE get_file