Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2024 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 = 0, icol1 = 0, icol2 = 0
87 : INTEGER :: input_unit = -1, input_line_number = 0
88 : LOGICAL :: first_separator = .TRUE., &
89 : apply_preprocessing = .FALSE., &
90 : parse_white_lines = .FALSE.
91 : CHARACTER(len=default_path_length), DIMENSION(:, :), POINTER :: initial_variables => NULL()
92 : TYPE(buffer_type), POINTER :: buffer => NULL()
93 : TYPE(status_type), POINTER :: status => NULL()
94 : TYPE(mp_para_env_type), POINTER :: para_env => NULL()
95 : TYPE(inpp_type), POINTER :: inpp => NULL()
96 : TYPE(ilist_type), POINTER :: ilist => NULL()
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 51168 : SUBROUTINE parser_release(parser)
109 : TYPE(cp_parser_type), INTENT(INOUT) :: parser
110 :
111 51168 : IF (parser%input_unit >= 0) THEN
112 27326 : CALL close_file(unit_number=parser%input_unit)
113 : END IF
114 51168 : CALL mp_para_env_release(parser%para_env)
115 51168 : CALL release_inpp_type(parser%inpp)
116 51168 : CALL release_ilist_type(parser%ilist)
117 51168 : CALL release_buffer_type(parser%buffer)
118 51168 : CALL release_status_type(parser%status)
119 51168 : IF (ASSOCIATED(parser%initial_variables)) THEN
120 86 : DEALLOCATE (parser%initial_variables)
121 : END IF
122 :
123 51168 : 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 153504 : SUBROUTINE parser_create(parser, file_name, unit_nr, para_env, end_section_label, &
145 : separator_chars, comment_char, continuation_char, quote_char, &
146 9124 : 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 : ! Load the default values and overwrite them, if requested
159 51168 : parser%separators = default_separators
160 51168 : IF (PRESENT(separator_chars)) parser%separators = separator_chars
161 153504 : parser%comment_character = default_comment_character
162 51168 : IF (PRESENT(comment_char)) parser%comment_character = comment_char
163 51168 : parser%continuation_character = default_continuation_character
164 51168 : IF (PRESENT(continuation_char)) parser%continuation_character = continuation_char
165 51168 : parser%quote_character = default_quote_character
166 51168 : IF (PRESENT(quote_char)) parser%quote_character = quote_char
167 51168 : parser%section_character = default_section_character
168 51168 : IF (PRESENT(section_char)) parser%section_character = section_char
169 51168 : parser%end_section = parser%section_character//default_end_section_label
170 51168 : IF (PRESENT(end_section_label)) THEN
171 0 : parser%end_section = parser%section_character//TRIM(end_section_label)
172 : END IF
173 51168 : parser%parse_white_lines = .FALSE.
174 51168 : IF (PRESENT(parse_white_lines)) THEN
175 1221 : parser%parse_white_lines = parse_white_lines
176 : END IF
177 51168 : parser%apply_preprocessing = .TRUE.
178 51168 : IF (PRESENT(apply_preprocessing)) THEN
179 730 : parser%apply_preprocessing = apply_preprocessing
180 : END IF
181 :
182 51168 : CALL compress(parser%end_section) ! needed?
183 :
184 : ! para_env
185 51168 : IF (PRESENT(para_env)) THEN
186 50918 : parser%para_env => para_env
187 50918 : CALL para_env%retain()
188 : ELSE
189 250 : ALLOCATE (parser%para_env)
190 250 : parser%para_env = mp_comm_self
191 : END IF
192 :
193 : ! Get the logical output unit number for error messages
194 51168 : IF (parser%para_env%is_source()) THEN
195 27326 : IF (PRESENT(unit_nr)) THEN
196 0 : parser%input_unit = unit_nr
197 0 : IF (PRESENT(file_name)) parser%input_file_name = TRIM(ADJUSTL(file_name))
198 : ELSE
199 27326 : IF (.NOT. PRESENT(file_name)) &
200 0 : CPABORT("at least one of filename and unit_nr must be present")
201 : CALL open_file(file_name=TRIM(ADJUSTL(file_name)), &
202 27326 : unit_number=parser%input_unit)
203 27326 : parser%input_file_name = TRIM(ADJUSTL(file_name))
204 : END IF
205 : END IF
206 :
207 51168 : IF (PRESENT(initial_variables)) THEN
208 9124 : IF (SIZE(initial_variables, 2) > 0) THEN
209 258 : ALLOCATE (parser%initial_variables(2, SIZE(initial_variables, 2)))
210 602 : parser%initial_variables = initial_variables
211 : END IF
212 : END IF
213 :
214 51168 : CALL create_inpp_type(parser%inpp, parser%initial_variables)
215 51168 : CALL create_ilist_type(parser%ilist)
216 51168 : CALL create_buffer_type(parser%buffer)
217 51168 : CALL create_status_type(parser%status)
218 51168 : END SUBROUTINE parser_create
219 :
220 : ! **************************************************************************************************
221 : !> \brief Resets the parser: rewinding the unit and re-initializing all
222 : !> parser structures
223 : !> \param parser ...
224 : !> \date 12.2008
225 : !> \author Teodoro Laino [tlaino]
226 : ! **************************************************************************************************
227 673 : SUBROUTINE parser_reset(parser)
228 : TYPE(cp_parser_type), INTENT(INOUT) :: parser
229 :
230 : ! Rewind units
231 673 : IF (parser%input_unit > 0) REWIND (parser%input_unit)
232 : ! Restore initial settings
233 673 : parser%input_line_number = 0
234 673 : parser%icol = 0
235 673 : parser%icol1 = 0
236 673 : parser%icol2 = 0
237 673 : parser%first_separator = .TRUE.
238 : ! Release substructures
239 673 : CALL release_inpp_type(parser%inpp)
240 673 : CALL release_ilist_type(parser%ilist)
241 673 : CALL release_buffer_type(parser%buffer)
242 673 : CALL release_status_type(parser%status)
243 : ! Reallocate substructures
244 673 : CALL create_inpp_type(parser%inpp, parser%initial_variables)
245 673 : CALL create_ilist_type(parser%ilist)
246 673 : CALL create_buffer_type(parser%buffer)
247 673 : CALL create_status_type(parser%status)
248 673 : END SUBROUTINE parser_reset
249 :
250 0 : END MODULE cp_parser_types
|