Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2023 CP2K developers group <https://cp2k.org> !
4 : ! !
5 : ! SPDX-License-Identifier: GPL-2.0-or-later !
6 : !--------------------------------------------------------------------------------------------------!
7 :
8 : ! **************************************************************************************************
9 : !> \brief Utility routines to read data from files.
10 : !> Kept as close as possible to the old parser because
11 : !> 1. string handling is a weak point of fortran compilers, and it is
12 : !> easy to write correct things that do not work
13 : !> 2. conversion of old code
14 : !> \par History
15 : !> 22.11.1999 first version of the old parser (called qs_parser)
16 : !> Matthias Krack
17 : !> 06.2004 removed module variables, cp_parser_type, new module [fawzi]
18 : !> 08.2008 Added buffering [tlaino]
19 : !> \author fawzi
20 : ! **************************************************************************************************
21 : MODULE cp_parser_types
22 : USE cp_files, ONLY: close_file,&
23 : open_file
24 : USE cp_parser_buffer_types, ONLY: buffer_type,&
25 : create_buffer_type,&
26 : release_buffer_type
27 : USE cp_parser_ilist_types, ONLY: create_ilist_type,&
28 : ilist_type,&
29 : release_ilist_type
30 : USE cp_parser_inpp_types, ONLY: create_inpp_type,&
31 : inpp_type,&
32 : release_inpp_type
33 : USE cp_parser_status_types, ONLY: create_status_type,&
34 : release_status_type,&
35 : status_type
36 : USE kinds, ONLY: default_path_length,&
37 : default_string_length,&
38 : max_line_length
39 : USE message_passing, ONLY: mp_comm_self,&
40 : mp_para_env_release,&
41 : mp_para_env_type
42 : USE string_utilities, ONLY: compress
43 : #include "../base/base_uses.f90"
44 :
45 : IMPLICIT NONE
46 :
47 : PRIVATE
48 :
49 : PUBLIC :: cp_parser_type, parser_release, parser_create, &
50 : parser_reset, empty_initial_variables
51 :
52 : ! this is a zero sized array by choice, and convenience
53 : CHARACTER(LEN=default_path_length), DIMENSION(2, 1:0) :: empty_initial_variables
54 :
55 : ! Private parameters
56 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_parser_types'
57 :
58 : ! Global variables
59 : CHARACTER(LEN=1), PARAMETER, PUBLIC :: default_continuation_character = CHAR(92) ! backslash
60 : CHARACTER(LEN=4), PARAMETER, PUBLIC :: default_separators = ",:;="
61 : CHARACTER(LEN=3), PARAMETER, PUBLIC :: default_end_section_label = "END"
62 : CHARACTER(LEN=1), PARAMETER, PUBLIC :: default_comment_character(2) = (/"#", "!"/), &
63 : default_section_character = "&", &
64 : default_quote_character = '"'
65 : INTEGER, PARAMETER, PUBLIC :: max_unit_number = 999
66 :
67 : ! **************************************************************************************************
68 : !> \brief represent a parser
69 : !> \param icol Number of the current column in the current input line,
70 : !> -1 if at the end of the file
71 : !> icol1 : First column of the current input string
72 : !> icol2 : Last column of the current input string
73 : !> \param input_line_number Number of the current input line read from the input file
74 : !> \param input_unit Logical unit number of the input file
75 : !> \author fawzi
76 : ! **************************************************************************************************
77 : TYPE cp_parser_type
78 : CHARACTER(LEN=default_string_length) :: end_section, start_section
79 : CHARACTER(LEN=10) :: separators
80 : CHARACTER(LEN=1) :: comment_character(2), &
81 : continuation_character, &
82 : quote_character, &
83 : section_character
84 : CHARACTER(LEN=default_path_length) :: input_file_name
85 : CHARACTER(LEN=max_line_length) :: input_line
86 : INTEGER :: icol, icol1, icol2
87 : INTEGER :: input_unit, input_line_number
88 : LOGICAL :: first_separator, &
89 : apply_preprocessing, &
90 : parse_white_lines
91 : CHARACTER(len=default_path_length), DIMENSION(:, :), POINTER :: initial_variables
92 : TYPE(buffer_type), POINTER :: buffer
93 : TYPE(status_type), POINTER :: status
94 : TYPE(mp_para_env_type), POINTER :: para_env
95 : TYPE(inpp_type), POINTER :: inpp
96 : TYPE(ilist_type), POINTER :: ilist
97 : END TYPE cp_parser_type
98 :
99 : CONTAINS
100 :
101 : ! **************************************************************************************************
102 : !> \brief releases the parser
103 : !> \param parser ...
104 : !> \date 14.02.2001
105 : !> \author MK
106 : !> \version 1.0
107 : ! **************************************************************************************************
108 48421 : SUBROUTINE parser_release(parser)
109 : TYPE(cp_parser_type), INTENT(INOUT) :: parser
110 :
111 48421 : IF (parser%input_unit >= 0) THEN
112 25933 : CALL close_file(unit_number=parser%input_unit)
113 : END IF
114 48421 : CALL mp_para_env_release(parser%para_env)
115 48421 : CALL release_inpp_type(parser%inpp)
116 48421 : CALL release_ilist_type(parser%ilist)
117 48421 : CALL release_buffer_type(parser%buffer)
118 48421 : CALL release_status_type(parser%status)
119 48421 : IF (ASSOCIATED(parser%initial_variables)) THEN
120 86 : DEALLOCATE (parser%initial_variables)
121 : END IF
122 :
123 48421 : END SUBROUTINE parser_release
124 :
125 : ! **************************************************************************************************
126 : !> \brief Start a parser run. Initial variables allow to @SET stuff before opening the file
127 : !> \param parser ...
128 : !> \param file_name ...
129 : !> \param unit_nr ...
130 : !> \param para_env ...
131 : !> \param end_section_label ...
132 : !> \param separator_chars ...
133 : !> \param comment_char ...
134 : !> \param continuation_char ...
135 : !> \param quote_char ...
136 : !> \param section_char ...
137 : !> \param parse_white_lines ...
138 : !> \param initial_variables ...
139 : !> \param apply_preprocessing ...
140 : !> \date 14.02.2001
141 : !> \author MK
142 : !> \version 1.0
143 : ! **************************************************************************************************
144 48421 : SUBROUTINE parser_create(parser, file_name, unit_nr, para_env, end_section_label, &
145 : separator_chars, comment_char, continuation_char, quote_char, &
146 8628 : section_char, parse_white_lines, initial_variables, apply_preprocessing)
147 : TYPE(cp_parser_type), INTENT(OUT) :: parser
148 : CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: file_name
149 : INTEGER, INTENT(in), OPTIONAL :: unit_nr
150 : TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
151 : CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: end_section_label, separator_chars
152 : CHARACTER(LEN=1), INTENT(IN), OPTIONAL :: comment_char, continuation_char, &
153 : quote_char, section_char
154 : LOGICAL, INTENT(IN), OPTIONAL :: parse_white_lines
155 : CHARACTER(len=*), DIMENSION(:, :), OPTIONAL :: initial_variables
156 : LOGICAL, INTENT(IN), OPTIONAL :: apply_preprocessing
157 :
158 48421 : parser%input_unit = -1
159 48421 : parser%input_file_name = ""
160 48421 : NULLIFY (parser%initial_variables)
161 :
162 : ! Load the default values and overwrite them, if requested
163 48421 : parser%separators = default_separators
164 48421 : IF (PRESENT(separator_chars)) parser%separators = separator_chars
165 145263 : parser%comment_character = default_comment_character
166 48421 : IF (PRESENT(comment_char)) parser%comment_character = comment_char
167 48421 : parser%continuation_character = default_continuation_character
168 48421 : IF (PRESENT(continuation_char)) parser%continuation_character = continuation_char
169 48421 : parser%quote_character = default_quote_character
170 48421 : IF (PRESENT(quote_char)) parser%quote_character = quote_char
171 48421 : parser%section_character = default_section_character
172 48421 : IF (PRESENT(section_char)) parser%section_character = section_char
173 48421 : parser%end_section = parser%section_character//default_end_section_label
174 48421 : IF (PRESENT(end_section_label)) THEN
175 0 : parser%end_section = parser%section_character//TRIM(end_section_label)
176 : END IF
177 48421 : parser%parse_white_lines = .FALSE.
178 48421 : IF (PRESENT(parse_white_lines)) THEN
179 1143 : parser%parse_white_lines = parse_white_lines
180 : END IF
181 48421 : parser%apply_preprocessing = .TRUE.
182 48421 : IF (PRESENT(apply_preprocessing)) THEN
183 14 : parser%apply_preprocessing = apply_preprocessing
184 : END IF
185 :
186 48421 : CALL compress(parser%end_section) ! needed?
187 :
188 : ! para_env
189 48421 : IF (PRESENT(para_env)) THEN
190 48183 : parser%para_env => para_env
191 48183 : CALL para_env%retain()
192 : ELSE
193 238 : ALLOCATE (parser%para_env)
194 238 : parser%para_env = mp_comm_self
195 : END IF
196 :
197 : ! *** Get the logical output unit number for error messages ***
198 48421 : IF (parser%para_env%is_source()) THEN
199 25933 : IF (PRESENT(unit_nr)) THEN
200 0 : parser%input_unit = unit_nr
201 0 : IF (PRESENT(file_name)) parser%input_file_name = file_name
202 : ELSE
203 25933 : IF (.NOT. PRESENT(file_name)) &
204 0 : CPABORT("at least one of filename and unit_nr must be present")
205 : CALL open_file(file_name=TRIM(file_name), &
206 25933 : unit_number=parser%input_unit)
207 25933 : parser%input_file_name = file_name
208 : END IF
209 : END IF
210 :
211 48421 : IF (PRESENT(initial_variables)) THEN
212 8628 : IF (SIZE(initial_variables, 2) > 0) THEN
213 258 : ALLOCATE (parser%initial_variables(2, SIZE(initial_variables, 2)))
214 602 : parser%initial_variables = initial_variables
215 : END IF
216 : END IF
217 :
218 48421 : parser%input_line_number = 0
219 48421 : parser%icol = 0
220 48421 : parser%icol1 = 0
221 48421 : parser%icol2 = 0
222 48421 : parser%first_separator = .TRUE.
223 48421 : NULLIFY (parser%buffer)
224 48421 : NULLIFY (parser%status)
225 48421 : NULLIFY (parser%inpp)
226 48421 : NULLIFY (parser%ilist)
227 48421 : CALL create_inpp_type(parser%inpp, parser%initial_variables)
228 48421 : CALL create_ilist_type(parser%ilist)
229 48421 : CALL create_buffer_type(parser%buffer)
230 48421 : CALL create_status_type(parser%status)
231 48421 : END SUBROUTINE parser_create
232 :
233 : ! **************************************************************************************************
234 : !> \brief Resets the parser: rewinding the unit and re-initializing all
235 : !> parser structures
236 : !> \param parser ...
237 : !> \date 12.2008
238 : !> \author Teodoro Laino [tlaino]
239 : ! **************************************************************************************************
240 510 : SUBROUTINE parser_reset(parser)
241 : TYPE(cp_parser_type), INTENT(INOUT) :: parser
242 :
243 : ! Rewind units
244 510 : IF (parser%input_unit > 0) REWIND (parser%input_unit)
245 : ! Restore initial settings
246 510 : parser%input_line_number = 0
247 510 : parser%icol = 0
248 510 : parser%icol1 = 0
249 510 : parser%icol2 = 0
250 510 : parser%first_separator = .TRUE.
251 : ! Release substructures
252 510 : CALL release_inpp_type(parser%inpp)
253 510 : CALL release_ilist_type(parser%ilist)
254 510 : CALL release_buffer_type(parser%buffer)
255 510 : CALL release_status_type(parser%status)
256 : ! Reallocate substructures
257 510 : CALL create_inpp_type(parser%inpp, parser%initial_variables)
258 510 : CALL create_ilist_type(parser%ilist)
259 510 : CALL create_buffer_type(parser%buffer)
260 510 : CALL create_status_type(parser%status)
261 510 : END SUBROUTINE parser_reset
262 :
263 0 : END MODULE cp_parser_types
|