Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
field_writer.f90
Go to the documentation of this file.
1! Copyright (c) 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!
33!
35
37 use num_types, only : rp, dp, sp
38 use json_module, only : json_file
41 use case, only : case_t
43 use json_utils, only : json_get
44 implicit none
45 private
46
48 type, public, extends(simulation_component_t) :: field_writer_t
50 type(fld_file_output_t), private :: output
51
52 contains
54 procedure, pass(this) :: init => field_writer_init_from_json
56 procedure, pass(this) :: init_from_attributes => &
59 procedure, pass(this) :: free => field_writer_free
61 procedure, pass(this) :: compute_ => field_writer_compute
62 end type field_writer_t
63
64contains
65
69 subroutine field_writer_init_from_json(this, json, case)
70 class(field_writer_t), intent(inout) :: this
71 type(json_file), intent(inout) :: json
72 class(case_t), intent(inout), target :: case
73 character(len=:), allocatable :: filename
74 character(len=:), allocatable :: precision
75 character(len=20), allocatable :: fields(:)
76
77 call this%init_base(json, case)
78 call json_get(json, "fields", fields)
79
80 if (json%valid_path("output_filename")) then
81 call json_get(json, "output_filename", filename)
82 if (json%valid_path("output_precision")) then
83 call json_get(json, "output_precision", precision)
84 if (precision == "double") then
85 call field_writer_init_from_attributes(this, fields, filename, dp)
86 else
87 call field_writer_init_from_attributes(this, fields, filename, sp)
88 end if
89 else
90 call field_writer_init_from_attributes(this, fields, filename)
91 end if
92 else
93 call field_writer_init_from_attributes(this, fields)
94 end if
95 end subroutine field_writer_init_from_json
96
103 subroutine field_writer_init_from_attributes(this, fields, filename, precision)
104 class(field_writer_t), intent(inout) :: this
105 character(len=20), allocatable, intent(in) :: fields(:)
106 character(len=*), intent(in), optional :: filename
107 integer, intent(in), optional :: precision
108 character(len=20) :: fieldi
109 integer :: i
110
111 ! Regsiter fields if they don't exist.
112 do i=1, size(fields)
113 fieldi = trim(fields(i))
114 call neko_field_registry%add_field(this%case%fluid%dm_Xh, fieldi,&
115 ignore_existing=.true.)
116 end do
117
118 if (present(filename)) then
119 if (present(precision)) then
120 call this%output%init(precision, filename, size(fields))
121 else
122 call this%output%init(sp, filename, size(fields))
123 end if
124 do i=1, size(fields)
125 fieldi = trim(fields(i))
126 call this%output%fields%assign(i, neko_field_registry%get_field(fieldi))
127 end do
128
129 call this%case%output_controller%add(this%output, &
130 this%output_controller%control_value, &
131 this%output_controller%control_mode)
132 else
133 do i=1, size(fields)
134 fieldi = trim(fields(i))
135 call this%case%f_out%fluid%append(neko_field_registry%get_field(fieldi))
136 end do
137 end if
138
140
142 subroutine field_writer_free(this)
143 class(field_writer_t), intent(inout) :: this
144 call this%free_base()
145 end subroutine field_writer_free
146
150 subroutine field_writer_compute(this, t, tstep)
151 class(field_writer_t), intent(inout) :: this
152 real(kind=rp), intent(in) :: t
153 integer, intent(in) :: tstep
154
155 end subroutine field_writer_compute
156
157end module field_writer
Retrieves a parameter by name or throws an error.
Defines a simulation case.
Definition case.f90:34
Defines a registry for storing solution fields.
type(field_registry_t), target, public neko_field_registry
Global field registry.
Implements the field_writer_t type.
subroutine field_writer_free(this)
Destructor.
subroutine field_writer_init_from_attributes(this, fields, filename, precision)
Actual constructor.
subroutine field_writer_init_from_json(this, json, case)
Constructor from json.
subroutine field_writer_compute(this, t, tstep)
Here to comply with the interface, does nothing.
Implements fld_file_output_t.
Utilities for retrieving parameters from the case files.
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
Simulation components are objects that encapsulate functionality that can be fit to a particular comp...
subroutine compute_(this, t, tstep)
Dummy compute function.
A simulation component that writes a 3d field to a file.
A simple output saving a list of fields to a .fld file.
Base abstract class for simulation components.