Neko 1.99.2
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
json_utils.f90
Go to the documentation of this file.
1! Copyright (c) 2019-2024, The Neko Authors
2! All rights reserved.
3!
4! Redistribution and use in source and binary forms, with or without
5! modification, are permitted provided that the following conditions
6! are met:
7!
8! * Redistributions of source code must retain the above copyright
9! notice, this list of conditions and the following disclaimer.
10!
11! * Redistributions in binary form must reproduce the above
12! copyright notice, this list of conditions and the following
13! disclaimer in the documentation and/or other materials provided
14! with the distribution.
15!
16! * Neither the name of the authors nor the names of its
17! contributors may be used to endorse or promote products derived
18! from this software without specific prior written permission.
19!
20! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31! POSSIBILITY OF SUCH DAMAGE.
32!
35 use num_types, only : rp, dp, sp
36 use json_module, only : json_file, json_value, json_core
37 use utils, only : neko_error
38 use math, only : abscmp
39 implicit none
40 private
41
44
46 logical :: json_no_defaults = .false.
47
54 end interface json_get
55
62 end interface json_get_or_default
63
66 end interface json_extract_item
67contains
68
73 subroutine json_get_real(json, name, value)
74 type(json_file), intent(inout) :: json
75 character(len=*), intent(in) :: name
76 real(kind=sp), intent(out) :: value
77
78 if (.not. json%valid_path(name)) then
79 call neko_error("Parameter " // name // " missing from the case file")
80 end if
81
82 call json%get(name, value)
83 end subroutine json_get_real
84
89 subroutine json_get_double(json, name, value)
90 type(json_file), intent(inout) :: json
91 character(len=*), intent(in) :: name
92 real(kind=dp), intent(out) :: value
93
94 if (.not. json%valid_path(name)) then
95 call neko_error("Parameter " // name // " missing from the case file")
96 end if
97
98 call json%get(name, value)
99 end subroutine json_get_double
100
105 subroutine json_get_integer(json, name, value)
106 type(json_file), intent(inout) :: json
107 character(len=*), intent(in) :: name
108 integer, intent(out) :: value
109
110 real(kind=rp) :: test_real
111
112 if (.not. json%valid_path(name)) then
113 call neko_error("Parameter " // name // " missing from the case file")
114 end if
115
116 call json%get(name, value)
117 call json%get(name, test_real)
118
119 if (.not. abscmp(real(value, kind=rp), test_real)) then
120 call neko_error("Parameter " // name // " is not an integer value")
121 end if
122
123
124 end subroutine json_get_integer
125
130 subroutine json_get_logical(json, name, value)
131 type(json_file), intent(inout) :: json
132 character(len=*), intent(in) :: name
133 logical, intent(out) :: value
134
135 if (.not. json%valid_path(name)) then
136 call neko_error("Parameter " // name // " missing from the case file")
137 end if
138
139 call json%get(name, value)
140 end subroutine json_get_logical
141
146 subroutine json_get_string(json, name, value)
147 type(json_file), intent(inout) :: json
148 character(len=*), intent(in) :: name
149 character(len=:), allocatable, intent(out) :: value
150
151 if (.not. json%valid_path(name)) then
152 call neko_error("Parameter " // name // " missing from the case file")
153 end if
154
155 call json%get(name, value)
156 end subroutine json_get_string
157
162 subroutine json_get_real_array(json, name, value)
163 type(json_file), intent(inout) :: json
164 character(len=*), intent(in) :: name
165 real(kind=sp), allocatable, intent(out) :: value(:)
166
167 if (.not. json%valid_path(name)) then
168 call neko_error("Parameter " // name // " missing from the case file")
169 end if
170
171 call json%get(name, value)
172 end subroutine json_get_real_array
173
178 subroutine json_get_double_array(json, name, value)
179 type(json_file), intent(inout) :: json
180 character(len=*), intent(in) :: name
181 real(kind=dp), allocatable, intent(out) :: value(:)
182
183 if (.not. json%valid_path(name)) then
184 call neko_error("Parameter " // name // " missing from the case file")
185 end if
186
187 call json%get(name, value)
188 end subroutine json_get_double_array
189
194 subroutine json_get_integer_array(json, name, value)
195 type(json_file), intent(inout) :: json
196 character(len=*), intent(in) :: name
197 integer, allocatable, intent(out) :: value(:)
198
199 real(kind=rp), allocatable :: test_real(:)
200 integer :: i
201
202 if (.not. json%valid_path(name)) then
203 call neko_error("Parameter " // name // " missing from the case file")
204 end if
205
206 call json%get(name, value)
207 call json%get(name, test_real)
208
209 do i = 1, size(value)
210 if (.not. abscmp(real(value(i), kind=rp), test_real(i))) then
211 call neko_error("Parameter " // name // " is not an integer array")
212 end if
213 end do
214 end subroutine json_get_integer_array
215
220 subroutine json_get_logical_array(json, name, value)
221 type(json_file), intent(inout) :: json
222 character(len=*), intent(in) :: name
223 logical, allocatable, intent(out) :: value(:)
224
225 if (.not. json%valid_path(name)) then
226 call neko_error("Parameter " // name // " missing from the case file")
227 end if
228
229 call json%get(name, value)
230 end subroutine json_get_logical_array
231
237 subroutine json_get_string_array(json, name, value, filler)
238 type(json_file), intent(inout) :: json
239 character(len=*), intent(in) :: name
240 character(len=*), allocatable, intent(out) :: value(:)
241 character(len=*), optional, intent(in) :: filler
242 logical :: found
243 type(json_value), pointer :: json_val, val_ptr
244 type(json_core) :: core
245 character(len=:), allocatable :: string_value
246 integer :: i, n_children
247
248 if (.not. json%valid_path(name)) then
249 call neko_error("Parameter " // name // " missing from the case file")
250 end if
251 call json%info(name, n_children = n_children)
252
253 if (.not. allocated(value)) then
254 allocate(value(n_children))
255 else if (len(value) .lt. n_children) then
256 deallocate(value)
257 allocate(value(n_children))
258 end if
259
260 call json%get(name, json_val, found)
261 call json%get_core(core)
262
263 do i = 1, n_children
264 call core%get_child(json_val, i, val_ptr, found)
265 call core%get(val_ptr, string_value)
266
267 if (len(string_value) .gt. 0) then
268 value(i) = string_value
269 else if (present(filler)) then
270 value(i) = filler
271 end if
272 end do
273
274 end subroutine json_get_string_array
275
277 subroutine json_get_subdict(json, key, output)
278 type(json_file), intent(inout) :: json
279 character(len=*), intent(in) :: key
280 type(json_file), intent(inout) :: output
281
282 type(json_value), pointer :: ptr
283 type(json_core) :: core
284 logical :: found
285 character(len=:), allocatable :: buffer
286
287 call json%get_core(core)
288 call json%get(key, ptr, found)
289
290 if (.not. found) then
291 call neko_error("Parameter " // &
292 trim(key) // " missing from the case file")
293 end if
294
295 call core%print_to_string(ptr, buffer)
296 call output%load_from_string(buffer)
297
298 end subroutine json_get_subdict
299
305 subroutine json_get_or_default_real(json, name, value, default)
306 type(json_file), intent(inout) :: json
307 character(len=*), intent(in) :: name
308 real(kind=sp), intent(out) :: value
309 real(kind=sp), intent(in) :: default
310 logical :: found
311
312 call json%get(name, value, found)
313
314 if ((.not. found) .and. (json_no_defaults .eqv. .false.)) then
315 value = default
316 call json%add(name, value)
317 else if (.not. found) then
318 call neko_error("Parameter " // name // " missing from the case file")
319 end if
320 end subroutine json_get_or_default_real
321
327 subroutine json_get_or_default_double(json, name, value, default)
328 type(json_file), intent(inout) :: json
329 character(len=*), intent(in) :: name
330 real(kind=dp), intent(out) :: value
331 real(kind=dp), intent(in) :: default
332 logical :: found
333
334 call json%get(name, value, found)
335
336 if ((.not. found) .and. (json_no_defaults .eqv. .false.)) then
337 value = default
338 call json%add(name, value)
339 else if (.not. found) then
340 call neko_error("Parameter " // name // " missing from the case file")
341 end if
342 end subroutine json_get_or_default_double
343
349 subroutine json_get_or_default_integer(json, name, value, default)
350 type(json_file), intent(inout) :: json
351 character(len=*), intent(in) :: name
352 integer, intent(out) :: value
353 integer, intent(in) :: default
354 logical :: found
355
356 call json%get(name, value, found)
357
358 if ((.not. found) .and. (json_no_defaults .eqv. .false.)) then
359 value = default
360 call json%add(name, value)
361 else if (.not. found) then
362 call neko_error("Parameter " // name // " missing from the case file")
363 end if
364 end subroutine json_get_or_default_integer
365
371 subroutine json_get_or_default_logical(json, name, value, default)
372 type(json_file), intent(inout) :: json
373 character(len=*), intent(in) :: name
374 logical, intent(out) :: value
375 logical, intent(in) :: default
376 logical :: found
377
378 call json%get(name, value, found)
379
380 if ((.not. found) .and. (json_no_defaults .eqv. .false.)) then
381 value = default
382 call json%add(name, value)
383 else if (.not. found) then
384 call neko_error("Parameter " // name // " missing from the case file")
385 end if
386 end subroutine json_get_or_default_logical
387
393 subroutine json_get_or_default_string(json, name, value, default)
394 type(json_file), intent(inout) :: json
395 character(len=*), intent(in) :: name
396 character(len=:), allocatable, intent(out) :: value
397 character(len=*), intent(in) :: default
398 logical :: found
399
400 call json%get(name, value, found)
401
402 if ((.not. found) .and. (json_no_defaults .eqv. .false.)) then
403 value = default
404 call json%add(name, value)
405 else if (.not. found) then
406 call neko_error("Parameter " // name // " missing from the case file")
407 end if
408 end subroutine json_get_or_default_string
409
415 subroutine json_extract_item_from_array(core, array, i, item)
416 type(json_core), intent(inout) :: core
417 type(json_value), pointer, intent(in) :: array
418 integer, intent(in) :: i
419 type(json_file), intent(inout) :: item
420 type(json_value), pointer :: ptr
421 logical :: found
422 character(len=:), allocatable :: buffer
423
424 call core%get_child(array, i, ptr, found)
425 call core%print_to_string(ptr, buffer)
426 call item%load_from_string(buffer)
427
428 end subroutine json_extract_item_from_array
429
435 subroutine json_extract_item_from_name(json, name, i, item)
436 type(json_file), intent(inout) :: json
437 character(len=*), intent(in) :: name
438 integer, intent(in) :: i
439 type(json_file), intent(out) :: item
440
441 type(json_core) :: core
442 type(json_value), pointer :: array
443 type(json_value), pointer :: ptr
444 logical :: found
445 character(len=:), allocatable :: buffer
446
447 call json%get_core(core)
448 call json%get(name, array, found)
449
450 if (.not. found) then
451 call neko_error("Parameter " // name // " missing from the case file")
452 end if
453
454 call core%get_child(array, i, ptr, found)
455 call core%print_to_string(ptr, buffer)
456 call item%load_from_string(buffer)
457
458 end subroutine json_extract_item_from_name
459
460end module json_utils
double real
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Retrieves a parameter by name or throws an error.
Generic buffer that is extended with buffers of varying rank.
Definition buffer.F90:34
Utilities for retrieving parameters from the case files.
subroutine json_extract_item_from_name(json, name, i, item)
Extract ith item from a JSON array as a separate JSON object.
subroutine json_get_logical(json, name, value)
Retrieves a logical parameter by name or throws an error.
subroutine json_get_or_default_string(json, name, value, default)
Retrieves a string parameter by name or assigns a provided default value. In the latter case also add...
subroutine json_get_real_array(json, name, value)
Retrieves a real array parameter by name or throws an error.
subroutine json_get_subdict(json, key, output)
Extract a sub-object from a json object.
subroutine json_extract_item_from_array(core, array, i, item)
Extract ith item from a JSON array as a separate JSON object.
subroutine json_get_string(json, name, value)
Retrieves a string parameter by name or throws an error.
subroutine json_get_or_default_real(json, name, value, default)
Retrieves a real parameter by name or assigns a provided default value. In the latter case also adds ...
subroutine json_get_or_default_double(json, name, value, default)
Retrieves a real parameter by name or assigns a provided default value. In the latter case also adds ...
subroutine json_get_or_default_logical(json, name, value, default)
Retrieves a logical parameter by name or assigns a provided default value. In the latter case also ad...
subroutine json_get_double_array(json, name, value)
Retrieves a real array parameter by name or throws an error.
subroutine json_get_or_default_integer(json, name, value, default)
Retrieves an integer parameter by name or assigns a provided default value. In the latter case also a...
subroutine json_get_double(json, name, value)
Retrieves a double precision real parameter by name or throws an error.
subroutine json_get_string_array(json, name, value, filler)
Retrieves a string array parameter by name or throws an error.
subroutine json_get_logical_array(json, name, value)
Retrieves a logical array parameter by name or throws an error.
subroutine json_get_real(json, name, value)
Retrieves a real parameter by name or throws an error.
logical, public json_no_defaults
If true, the json_get_or_default routines will not add missing parameters.
subroutine json_get_integer(json, name, value)
Retrieves an integer parameter by name or throws an error.
subroutine json_get_integer_array(json, name, value)
Retrieves a integer array parameter by name or throws an error.
Definition math.f90:60
integer, parameter, public dp
Definition num_types.f90:9
integer, parameter, public sp
Definition num_types.f90:8
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines an output.
Definition output.f90:34
Utilities.
Definition utils.f90:35