File: xml_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 (175 lines) | stat: -rw-r--r-- 6,998 bytes parent folder | download
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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
!
! Copyright (C) 2002-2005 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 xml_input

   USE xml_io_base, ONLY : attr
   USE iotk_module
   USE kinds

   IMPLICIT NONE
   PRIVATE
   
   PUBLIC :: xml_input_dump

   INTERFACE dump_keyword
      MODULE PROCEDURE dump_keyword_str, dump_keyword_i
   END INTERFACE

   CONTAINS

   SUBROUTINE xml_input_dump
      
      USE io_global,        ONLY : ionode, stdout
      USE io_files,         ONLY : iunpun
      USE global_version,   ONLY : version_number
      USE input_parameters

      CHARACTER(LEN=256) :: filename
      INTEGER            :: ierr

      return

      filename = 'qe_input.xml'
      
      IF ( ionode ) THEN
         !
         ! ... Open XML descriptor
         !
         WRITE( stdout, '(/,3X,"Dumping input parameters",/)' )
         !
         CALL iotk_open_write( iunpun, FILE = filename, BINARY = .FALSE., IERR = ierr )
         !
      END IF

      IF ( ionode ) THEN

         CALL iotk_write_attr( attr, "targetNamespace", "http://www.deisa.org/pwscf/3_2", FIRST = .TRUE. )
         CALL iotk_write_attr( attr, "elementFormDefault", "qualified" )
         CALL iotk_write_attr( attr, "xmlns", "http://www.w3.org/2001/XMLSchema" )
         CALL iotk_write_attr( attr, "xmlns:tns", "http://www.deisa.org/pwscf/3_2" )
         CALL iotk_write_begin( iunpun, "schema", attr )

         CALL write_header( "Quantum ESPRESSO", TRIM(version_number) )

         CALL iotk_write_attr( attr, "section_type", "namelist", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "CONTROLS", attr )
           CALL dump_keyword( "title", title, "namelist", " " )
           CALL dump_keyword( "calculation", calculation, "namelist", " ", calculation_allowed )
           CALL dump_keyword( "verbosity", verbosity, "namelist", " ", verbosity_allowed )
           CALL dump_keyword( "restart_mode", restart_mode, "namelist", " ", restart_mode_allowed )
           CALL dump_keyword( "nstep", nstep, "namelist", " ", min_value = 1 )
           CALL dump_keyword( "iprint", iprint, "namelist", " ", min_value = 1 )
         CALL iotk_write_end( iunpun, "CONTROLS" )

         CALL iotk_write_attr( attr, "section_type", "namelist", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "SYSTEM", attr )
         CALL iotk_write_end( iunpun, "SYSTEM" )

         CALL iotk_write_attr( attr, "section_type", "namelist", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "ELECTRONS", attr )
         CALL iotk_write_end( iunpun, "ELECTRONS" )

         CALL iotk_write_attr( attr, "section_type", "namelist", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "IONS", attr )
         CALL iotk_write_end( iunpun, "IONS" )

         CALL iotk_write_attr( attr, "section_type", "namelist", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "CELL", attr )
         CALL iotk_write_end( iunpun, "CELL" )

         CALL iotk_write_attr( attr, "section_type", "card", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "ATOMIC_SPECIES", attr )
         CALL iotk_write_end( iunpun, "ATOMIC_SPECIES" )

         CALL iotk_write_attr( attr, "section_type", "card", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "ATOMIC_POSITIONS", attr )
         CALL iotk_write_end( iunpun, "ATOMIC_POSITIONS" )

         CALL iotk_write_attr( attr, "section_type", "card", FIRST = .TRUE. )
         CALL iotk_write_begin( iunpun, "K_POINTS", attr )
         CALL iotk_write_end( iunpun, "K_POINTS" )

         CALL iotk_write_end( iunpun, "schema" )

      END IF

      IF ( ionode ) CALL iotk_close_write( iunpun )

      RETURN
   END SUBROUTINE


   SUBROUTINE dump_keyword_str( kname, defval, usage, descr, allowed )
      USE io_files,         ONLY : iunpun
      CHARACTER(LEN=*) :: kname
      CHARACTER(LEN=*) :: defval
      CHARACTER(LEN=*) :: usage
      CHARACTER(LEN=*) :: descr
      CHARACTER(LEN=*), OPTIONAL :: allowed(:)
         CALL iotk_write_attr( attr, "required", "no", FIRST = .TRUE. )
         CALL iotk_write_attr( attr, "repeat", "no")
         CALL iotk_write_begin( iunpun, "KEYWORD", ATTR = attr )
         CALL iotk_write_attr( attr, "type", "default", FIRST = .TRUE. )
         CALL iotk_write_dat( iunpun, "NAME", kname, ATTR = attr )
         CALL iotk_write_attr( attr, "kind", "STRING", FIRST = .TRUE. )  ! type
         CALL iotk_write_begin( iunpun, "DATA_TYPE", ATTR = attr )
         CALL iotk_write_dat( iunpun, "N_VAR", 1 )
         CALL iotk_write_end( iunpun, "DATA_TYPE" )
         IF( usage == "namelist" ) THEN
            CALL iotk_write_dat( iunpun, "USAGE", kname//" = value" )
         ELSE
            CALL iotk_write_dat( iunpun, "USAGE", usage )
         END IF
         IF( PRESENT( allowed ) ) THEN
            CALL iotk_write_dat( iunpun, "ALLOWED_VALUES", allowed )
         END IF
         CALL iotk_write_dat( iunpun, "DESCRIPTION", descr )
         CALL iotk_write_dat( iunpun, "DEFAULT_VALUE", defval )
         CALL iotk_write_end( iunpun, "KEYWORD" )
      RETURN
   END SUBROUTINE

   SUBROUTINE dump_keyword_i( kname, defval, usage, descr, min_value, max_value )
      USE io_files,         ONLY : iunpun
      CHARACTER(LEN=*) :: kname
      INTEGER          :: defval                                         ! type
      CHARACTER(LEN=*) :: usage
      CHARACTER(LEN=*) :: descr
      INTEGER, OPTIONAL :: min_value                                  ! type
      INTEGER, OPTIONAL :: max_value                                  ! type
         CALL iotk_write_attr( attr, "required", "no", FIRST = .TRUE. )
         CALL iotk_write_attr( attr, "repeat", "no")
         CALL iotk_write_begin( iunpun, "KEYWORD", ATTR = attr )
         CALL iotk_write_attr( attr, "type", "default", FIRST = .TRUE. )
         CALL iotk_write_dat( iunpun, "NAME", kname, ATTR = attr )
         CALL iotk_write_attr( attr, "kind", "INTEGER", FIRST = .TRUE. )  ! type
         CALL iotk_write_begin( iunpun, "DATA_TYPE", ATTR = attr )
         CALL iotk_write_dat( iunpun, "N_VAR", 1 )
         CALL iotk_write_end( iunpun, "DATA_TYPE" )
         IF( usage == "namelist" ) THEN
            CALL iotk_write_dat( iunpun, "USAGE", kname//" = value" )
         ELSE
            CALL iotk_write_dat( iunpun, "USAGE", usage )
         END IF
         IF( PRESENT( min_value ) ) THEN
            CALL iotk_write_dat( iunpun, "MIN_VALUE", min_value )
         END IF
         IF( PRESENT( max_value ) ) THEN
            CALL iotk_write_dat( iunpun, "MAX_VALUE", max_value )
         END IF
         CALL iotk_write_dat( iunpun, "DESCRIPTION", descr )
         CALL iotk_write_dat( iunpun, "DEFAULT_VALUE", defval )
         CALL iotk_write_end( iunpun, "KEYWORD" )
      RETURN
   END SUBROUTINE


END MODULE