File: read_input.f90

package info (click to toggle)
espresso 5.1%2Bdfsg-3
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 146,004 kB
  • ctags: 17,245
  • sloc: f90: 253,041; sh: 51,271; ansic: 27,494; tcl: 15,570; xml: 14,508; makefile: 2,958; perl: 2,035; fortran: 1,924; python: 337; cpp: 200; awk: 57
file content (83 lines) | stat: -rw-r--r-- 2,525 bytes parent folder | download | duplicates (2)
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
75
76
77
78
79
80
81
82
83
!
! Copyright (C) 2011 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 .
!
!----------------------------------------------------------------------------
MODULE read_input
   !---------------------------------------------------------------------------
   !
   USE kinds,     ONLY: DP
   !
   IMPLICIT NONE
   SAVE
   !
   PRIVATE
   PUBLIC :: read_input_file, has_been_read
   !
   LOGICAL :: has_been_read = .FALSE.
   !
   CONTAINS
   !
   !-------------------------------------------------------------------------
   SUBROUTINE read_input_file ( prog, input_file_ )
     !-------------------------------------------------------------------------
     !
     USE input_parameters,      ONLY : reset_input_checks
     USE read_namelists_module, ONLY : read_namelists
     USE read_cards_module,     ONLY : read_cards
     USE io_global,             ONLY : ionode, ionode_id, qestdin
     USE xml_input,             ONLY : xml_input_dump
     USE read_xml_module,       ONLY : read_xml
     USE mp,                    ONLY : mp_bcast
     USE mp_images,             ONLY : intra_image_comm
     USE iotk_module,           ONLY : iotk_attlenx
     USE open_close_input_file, ONLY : open_input_file, close_input_file
     !
     IMPLICIT NONE
     !
     CHARACTER(LEN=2), INTENT (IN) :: prog
     CHARACTER(LEN=*), INTENT (IN) :: input_file_
     !
     CHARACTER(LEN=iotk_attlenx) :: attr
     LOGICAL :: xmlinput
     INTEGER :: ierr
     !
     IF ( ionode ) THEN
        IF ( prog == 'CP' ) CALL xml_input_dump()
        ierr = open_input_file( input_file_, xmlinput, attr) 
     END IF
     !
     CALL mp_bcast( ierr, ionode_id, intra_image_comm )
     IF ( ierr > 0 ) CALL errore('read_input', 'opening input file',ierr)
     CALL mp_bcast( xmlinput, ionode_id, intra_image_comm )
     CALL mp_bcast( attr, ionode_id, intra_image_comm )
     !
     CALL reset_input_checks () 
     !
     IF ( xmlinput ) THEN
        !
        CALL read_xml ( prog, attr )
        !
     ELSE
        !
        ! ... Read NAMELISTS 
        !
        CALL read_namelists( prog, qestdin )
        !
        ! ... Read CARDS 
        !
        CALL read_cards ( prog, qestdin )
        !
     END IF
     IF ( ionode) ierr = close_input_file( )
     !
     has_been_read = .TRUE.
     !
     RETURN
     !
   END SUBROUTINE read_input_file
  !
END MODULE read_input