Neko  0.8.1
A portable framework for high-order spectral element flow simulations
json_utils.f90
Go to the documentation of this file.
1 ! Copyright (c) 2019-2021, 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 !
34 module json_utils
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  implicit none
39  private
40 
42 
44  interface json_get
45  module procedure json_get_real, json_get_double, json_get_integer, &
49  end interface json_get
50 
57  end interface json_get_or_default
58 
59 contains
60 
65  subroutine json_get_real(json, name, value)
66  type(json_file), intent(inout) :: json
67  character(len=*), intent(in) :: name
68  real(kind=sp), intent(out) :: value
69  logical :: found
70 
71  call json%get(name, value, found)
72 
73  if (.not. found) then
74  call neko_error("Parameter "//name//" missing from the case file")
75  end if
76  end subroutine json_get_real
77 
82  subroutine json_get_double(json, name, value)
83  type(json_file), intent(inout) :: json
84  character(len=*), intent(in) :: name
85  real(kind=dp), intent(out) :: value
86  logical :: found
87 
88  call json%get(name, value, found)
89 
90  if (.not. found) then
91  call neko_error("Parameter "//name//" missing from the case file")
92  end if
93  end subroutine json_get_double
94 
99  subroutine json_get_integer(json, name, value)
100  type(json_file), intent(inout) :: json
101  character(len=*), intent(in) :: name
102  integer, intent(out) :: value
103  logical :: found
104 
105  call json%get(name, value, found)
106 
107  if (.not. found) then
108  call neko_error("Parameter "//name//" missing from the case file")
109  end if
110  end subroutine json_get_integer
111 
116  subroutine json_get_logical(json, name, value)
117  type(json_file), intent(inout) :: json
118  character(len=*), intent(in) :: name
119  logical, intent(out) :: value
120  logical :: found
121 
122  call json%get(name, value, found)
123 
124  if (.not. found) then
125  call neko_error("Parameter "//name//" missing from the case file")
126  end if
127  end subroutine json_get_logical
128 
133  subroutine json_get_string(json, name, value)
134  type(json_file), intent(inout) :: json
135  character(len=*), intent(in) :: name
136  character(len=:), allocatable, intent(out) :: value
137  logical :: found
138 
139  call json%get(name, value, found)
140 
141  if (.not. found) then
142  call neko_error("Parameter "//name//" missing from the case file")
143  end if
144  end subroutine json_get_string
145 
150  subroutine json_get_real_array(json, name, value)
151  type(json_file), intent(inout) :: json
152  character(len=*), intent(in) :: name
153  real(kind=sp), allocatable, intent(out) :: value(:)
154  logical :: found
155 
156  call json%get(name, value, found)
157 
158  if (.not. found) then
159  call neko_error("Parameter "//name//" missing from the case file")
160  end if
161  end subroutine json_get_real_array
162 
167  subroutine json_get_double_array(json, name, value)
168  type(json_file), intent(inout) :: json
169  character(len=*), intent(in) :: name
170  real(kind=dp), allocatable, intent(out) :: value(:)
171  logical :: found
172 
173  call json%get(name, value, found)
174 
175  if (.not. found) then
176  call neko_error("Parameter "//name//" missing from the case file")
177  end if
178  end subroutine json_get_double_array
179 
184  subroutine json_get_integer_array(json, name, value)
185  type(json_file), intent(inout) :: json
186  character(len=*), intent(in) :: name
187  integer, allocatable, intent(out) :: value(:)
188  logical :: found
189 
190  call json%get(name, value, found)
191 
192  if (.not. found) then
193  call neko_error("Parameter "//name//" missing from the case file")
194  end if
195  end subroutine json_get_integer_array
196 
201  subroutine json_get_logical_array(json, name, value)
202  type(json_file), intent(inout) :: json
203  character(len=*), intent(in) :: name
204  logical, allocatable, intent(out) :: value(:)
205  logical :: found
206 
207  call json%get(name, value, found)
208 
209  if (.not. found) then
210  call neko_error("Parameter "//name//" missing from the case file")
211  end if
212  end subroutine json_get_logical_array
213 
219  subroutine json_get_string_array(json, name, value, filler)
220  type(json_file), intent(inout) :: json
221  character(len=*), intent(in) :: name
222  character(len=*), allocatable, intent(out) :: value(:)
223  character(len=*), optional, intent(in) :: filler
224  logical :: found
225  type(json_value), pointer :: json_val, val_ptr
226  type(json_core) :: core
227  character(len=:), allocatable :: string_value
228  integer :: i, n_children
229 
230  if (.not. json%valid_path(name)) then
231  call neko_error("Parameter "//name//" missing from the case file")
232  end if
233  call json%info(name, n_children=n_children)
234 
235  if (.not. allocated(value)) then
236  allocate(value(n_children))
237  else if (len(value) .lt. n_children) then
238  deallocate(value)
239  allocate(value(n_children))
240  end if
241 
242  call json%get(name, json_val, found)
243  call json%get_core(core)
244 
245  do i = 1, n_children
246  call core%get_child(json_val, i, val_ptr, found)
247  call core%get(val_ptr, string_value)
248 
249  if (len(string_value) .gt. 0) then
250  value(i) = string_value
251  else if(present(filler)) then
252  value(i) = filler
253  end if
254  end do
255 
256  end subroutine json_get_string_array
257 
263  subroutine json_get_or_default_real(json, name, value, default)
264  type(json_file), intent(inout) :: json
265  character(len=*), intent(in) :: name
266  real(kind=sp), intent(out) :: value
267  real(kind=sp), intent(in) :: default
268  logical :: found
269 
270  call json%get(name, value, found)
271 
272  if (.not. found) then
273  value = default
274  call json%add(name, value)
275  end if
276  end subroutine json_get_or_default_real
277 
283  subroutine json_get_or_default_double(json, name, value, default)
284  type(json_file), intent(inout) :: json
285  character(len=*), intent(in) :: name
286  real(kind=dp), intent(out) :: value
287  real(kind=dp), intent(in) :: default
288  logical :: found
289 
290  call json%get(name, value, found)
291 
292  if (.not. found) then
293  value = default
294  call json%add(name, value)
295  end if
296  end subroutine json_get_or_default_double
297 
303  subroutine json_get_or_default_integer(json, name, value, default)
304  type(json_file), intent(inout) :: json
305  character(len=*), intent(in) :: name
306  integer, intent(out) :: value
307  integer, intent(in) :: default
308  logical :: found
309 
310  call json%get(name, value, found)
311 
312  if (.not. found) then
313  value = default
314  call json%add(name, value)
315  end if
316  end subroutine json_get_or_default_integer
317 
323  subroutine json_get_or_default_logical(json, name, value, default)
324  type(json_file), intent(inout) :: json
325  character(len=*), intent(in) :: name
326  logical, intent(out) :: value
327  logical, intent(in) :: default
328  logical :: found
329 
330  call json%get(name, value, found)
331 
332  if (.not. found) then
333  value = default
334  call json%add(name, value)
335  end if
336  end subroutine json_get_or_default_logical
337 
343  subroutine json_get_or_default_string(json, name, value, default)
344  type(json_file), intent(inout) :: json
345  character(len=*), intent(in) :: name
346  character(len=:), allocatable, intent(out) :: value
347  character(len=*), intent(in) :: default
348  logical :: found
349 
350  call json%get(name, value, found)
351 
352  if (.not. found) then
353  value = default
354  call json%add(name, value)
355  end if
356  end subroutine json_get_or_default_string
357 
363  subroutine json_extract_item(core, array, i, item)
364  type(json_core), intent(inout) :: core
365  type(json_value), pointer, intent(in) :: array
366  integer, intent(in) :: i
367  type(json_file), intent(inout) :: item
368  type(json_value), pointer :: ptr
369  logical :: found
370  character(len=:), allocatable :: buffer
371 
372  call core%get_child(array, i, ptr, found)
373  call core%print_to_string(ptr, buffer)
374  call item%load_from_string(buffer)
375 
376  end subroutine json_extract_item
377 
378 end module json_utils
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Definition: json_utils.f90:53
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
subroutine json_get_logical(json, name, value)
Retrieves a logical parameter by name or throws an error.
Definition: json_utils.f90:117
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...
Definition: json_utils.f90:344
subroutine, public json_extract_item(core, array, i, item)
Extract ith item from a JSON array as a separate JSON object.
Definition: json_utils.f90:364
subroutine json_get_real_array(json, name, value)
Retrieves a real array parameter by name or throws an error.
Definition: json_utils.f90:151
subroutine json_get_string(json, name, value)
Retrieves a string parameter by name or throws an error.
Definition: json_utils.f90:134
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 ...
Definition: json_utils.f90:264
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 ...
Definition: json_utils.f90:284
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...
Definition: json_utils.f90:324
subroutine json_get_double_array(json, name, value)
Retrieves a real array parameter by name or throws an error.
Definition: json_utils.f90:168
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...
Definition: json_utils.f90:304
subroutine json_get_double(json, name, value)
Retrieves a double precision real parameter by name or throws an error.
Definition: json_utils.f90:83
subroutine json_get_string_array(json, name, value, filler)
Retrieves a string array parameter by name or throws an error.
Definition: json_utils.f90:220
subroutine json_get_logical_array(json, name, value)
Retrieves a logical array parameter by name or throws an error.
Definition: json_utils.f90:202
subroutine json_get_real(json, name, value)
Retrieves a real parameter by name or throws an error.
Definition: json_utils.f90:66
subroutine json_get_integer(json, name, value)
Retrieves an integer parameter by name or throws an error.
Definition: json_utils.f90:100
subroutine json_get_integer_array(json, name, value)
Retrieves a integer array parameter by name or throws an error.
Definition: json_utils.f90:185
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
Utilities.
Definition: utils.f90:35