43#include "../base/base_uses.f90"
56 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'cp_parser_types'
65 INTEGER,
PARAMETER,
PUBLIC :: max_unit_number = 999
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()
111 IF (parser%input_unit >= 0)
THEN
112 CALL close_file(unit_number=parser%input_unit)
119 IF (
ASSOCIATED(parser%initial_variables))
THEN
120 DEALLOCATE (parser%initial_variables)
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)
148 CHARACTER(LEN=*),
INTENT(IN),
OPTIONAL :: file_name
149 INTEGER,
INTENT(in),
OPTIONAL :: unit_nr
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
160 IF (
PRESENT(separator_chars)) parser%separators = separator_chars
162 IF (
PRESENT(comment_char)) parser%comment_character = comment_char
164 IF (
PRESENT(continuation_char)) parser%continuation_character = continuation_char
166 IF (
PRESENT(quote_char)) parser%quote_character = quote_char
168 IF (
PRESENT(section_char)) parser%section_character = section_char
170 IF (
PRESENT(end_section_label))
THEN
171 parser%end_section = parser%section_character//trim(end_section_label)
173 parser%parse_white_lines = .false.
174 IF (
PRESENT(parse_white_lines))
THEN
175 parser%parse_white_lines = parse_white_lines
177 parser%apply_preprocessing = .true.
178 IF (
PRESENT(apply_preprocessing))
THEN
179 parser%apply_preprocessing = apply_preprocessing
185 IF (
PRESENT(para_env))
THEN
186 parser%para_env => para_env
187 CALL para_env%retain()
189 ALLOCATE (parser%para_env)
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 = trim(adjustl(file_name))
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(adjustl(file_name)), &
202 unit_number=parser%input_unit)
203 parser%input_file_name = trim(adjustl(file_name))
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
231 IF (parser%input_unit > 0) rewind(parser%input_unit)
233 parser%input_line_number = 0
237 parser%first_separator = .true.
Utility routines to open and close files. Tracking of preconnections.
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.
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.
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.
integer, parameter, public max_line_length
integer, parameter, public default_string_length
integer, parameter, public default_path_length
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