(git:374b731)
Loading...
Searching...
No Matches
cp_parser_types.F
Go to the documentation of this file.
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! **************************************************************************************************
22 USE cp_files, ONLY: close_file,&
31 inpp_type,&
36 USE kinds, ONLY: default_path_length,&
39 USE message_passing, ONLY: mp_comm_self,&
42 USE string_utilities, ONLY: compress
43#include "../base/base_uses.f90"
44
45 IMPLICIT NONE
46
47 PRIVATE
48
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) = (/"#", "!"/), &
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! **************************************************************************************************
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
99CONTAINS
100
101! **************************************************************************************************
102!> \brief releases the parser
103!> \param parser ...
104!> \date 14.02.2001
105!> \author MK
106!> \version 1.0
107! **************************************************************************************************
108 SUBROUTINE parser_release(parser)
109 TYPE(cp_parser_type), INTENT(INOUT) :: parser
110
111 IF (parser%input_unit >= 0) THEN
112 CALL close_file(unit_number=parser%input_unit)
113 END IF
114 CALL mp_para_env_release(parser%para_env)
115 CALL release_inpp_type(parser%inpp)
116 CALL release_ilist_type(parser%ilist)
117 CALL release_buffer_type(parser%buffer)
118 CALL release_status_type(parser%status)
119 IF (ASSOCIATED(parser%initial_variables)) THEN
120 DEALLOCATE (parser%initial_variables)
121 END IF
122
123 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 SUBROUTINE parser_create(parser, file_name, unit_nr, para_env, end_section_label, &
145 separator_chars, comment_char, continuation_char, quote_char, &
146 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 parser%separators = default_separators
160 IF (PRESENT(separator_chars)) parser%separators = separator_chars
161 parser%comment_character = default_comment_character
162 IF (PRESENT(comment_char)) parser%comment_character = comment_char
163 parser%continuation_character = default_continuation_character
164 IF (PRESENT(continuation_char)) parser%continuation_character = continuation_char
165 parser%quote_character = default_quote_character
166 IF (PRESENT(quote_char)) parser%quote_character = quote_char
167 parser%section_character = default_section_character
168 IF (PRESENT(section_char)) parser%section_character = section_char
169 parser%end_section = parser%section_character//default_end_section_label
170 IF (PRESENT(end_section_label)) THEN
171 parser%end_section = parser%section_character//trim(end_section_label)
172 END IF
173 parser%parse_white_lines = .false.
174 IF (PRESENT(parse_white_lines)) THEN
175 parser%parse_white_lines = parse_white_lines
176 END IF
177 parser%apply_preprocessing = .true.
178 IF (PRESENT(apply_preprocessing)) THEN
179 parser%apply_preprocessing = apply_preprocessing
180 END IF
181
182 CALL compress(parser%end_section) ! needed?
183
184 ! para_env
185 IF (PRESENT(para_env)) THEN
186 parser%para_env => para_env
187 CALL para_env%retain()
188 ELSE
189 ALLOCATE (parser%para_env)
190 parser%para_env = mp_comm_self
191 END IF
192
193 ! *** Get the logical output unit number for error messages ***
194 IF (parser%para_env%is_source()) THEN
195 IF (PRESENT(unit_nr)) THEN
196 parser%input_unit = unit_nr
197 IF (PRESENT(file_name)) parser%input_file_name = file_name
198 ELSE
199 IF (.NOT. PRESENT(file_name)) &
200 cpabort("at least one of filename and unit_nr must be present")
201 CALL open_file(file_name=trim(file_name), &
202 unit_number=parser%input_unit)
203 parser%input_file_name = file_name
204 END IF
205 END IF
206
207 IF (PRESENT(initial_variables)) THEN
208 IF (SIZE(initial_variables, 2) > 0) THEN
209 ALLOCATE (parser%initial_variables(2, SIZE(initial_variables, 2)))
210 parser%initial_variables = initial_variables
211 END IF
212 END IF
213
214 CALL create_inpp_type(parser%inpp, parser%initial_variables)
215 CALL create_ilist_type(parser%ilist)
216 CALL create_buffer_type(parser%buffer)
217 CALL create_status_type(parser%status)
218 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 SUBROUTINE parser_reset(parser)
228 TYPE(cp_parser_type), INTENT(INOUT) :: parser
229
230 ! Rewind units
231 IF (parser%input_unit > 0) rewind(parser%input_unit)
232 ! Restore initial settings
233 parser%input_line_number = 0
234 parser%icol = 0
235 parser%icol1 = 0
236 parser%icol2 = 0
237 parser%first_separator = .true.
238 ! Release substructures
239 CALL release_inpp_type(parser%inpp)
240 CALL release_ilist_type(parser%ilist)
241 CALL release_buffer_type(parser%buffer)
242 CALL release_status_type(parser%status)
243 ! Reallocate substructures
244 CALL create_inpp_type(parser%inpp, parser%initial_variables)
245 CALL create_ilist_type(parser%ilist)
246 CALL create_buffer_type(parser%buffer)
247 CALL create_status_type(parser%status)
248 END SUBROUTINE parser_reset
249
250END MODULE cp_parser_types
Utility routines to open and close files. Tracking of preconnections.
Definition cp_files.F:16
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
Definition cp_files.F:308
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
Definition cp_files.F:119
a module to allow simple buffering of read lines of a parser
subroutine, public create_buffer_type(buffer)
Creates the parser buffer type.
recursive subroutine, public release_buffer_type(buffer)
Releases the parser buffer type.
a module to allow simple internal preprocessing in input files.
subroutine, public release_ilist_type(ilist)
creates the integer listing type
subroutine, public create_ilist_type(ilist)
creates the integer listing type
a module to allow simple internal preprocessing in input files.
subroutine, public create_inpp_type(inpp, initial_variables)
creates the internal preprocessing type
subroutine, public release_inpp_type(inpp)
releases the internal preprocessing type
a module to allow the storage of the parser status
subroutine, public create_status_type(status)
creates the parser status type
subroutine, public release_status_type(status)
releases the parser status type
Utility routines to read data from files. Kept as close as possible to the old parser because.
character(len=default_path_length), dimension(2, 1:0), public empty_initial_variables
character(len=1), parameter, public default_quote_character
character(len=1), dimension(2), parameter, public default_comment_character
subroutine, public parser_reset(parser)
Resets the parser: rewinding the unit and re-initializing all parser structures.
subroutine, public parser_release(parser)
releases the parser
character(len=4), parameter, public default_separators
character(len=1), parameter, public default_continuation_character
character(len=1), parameter, public default_section_character
character(len=3), parameter, public default_end_section_label
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public max_line_length
Definition kinds.F:59
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Interface to the message passing library MPI.
subroutine, public mp_para_env_release(para_env)
releases the para object (to be called when you don't want anymore the shared copy of this object)
type(mp_comm_type), parameter, public mp_comm_self
Utilities for string manipulations.
subroutine, public compress(string, full)
Eliminate multiple space characters in a string. If full is .TRUE., then all spaces are eliminated.
Buffer type for speeding-up the parsing in parallel.
stores all the informations relevant to an mpi environment