Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
design_3dto1d.f90
Go to the documentation of this file.
1
34
35! Implements the `design_3dto1d_t` type.
36module design_3dto1d
37 use num_types, only: rp, sp
38 use json_module, only: json_file
39 use mapping, only: mapping_t
40 use pde_filter, only: pde_filter_t
42 use coefs, only: coef_t
43 use scratch_registry, only: neko_scratch_registry
44 use point_zone_registry, only: neko_point_zone_registry
45 use point_zone, only: point_zone_t
47 use neko_config, only: neko_bcknd_device
48 use device, only: device_memcpy, host_to_device, device_to_host
49 use device_math, only: device_copy
50 use design, only: design_t
51 use math, only: rzero
52 use simulation_m, only: simulation_t
53 use json_module, only: json_file
54 use json_utils, only: json_get
55 use utils, only: neko_error
56
57 use vector, only: vector_t
58 use math, only: copy
59
60 use mpi_f08, only: mpi_exscan, mpi_sum, mpi_integer, mpi_allreduce
61 use comm, only: pe_rank, pe_size, neko_comm, mpi_real_precision
62
63 use fld_file_output, only: fld_file_output_t
64
65 implicit none
66 private
67
69 type, extends(design_t), public :: design_3dto1d_t
70 private
71
72 type(vector_t) :: values
73
74 contains
75
76 ! ----------------------------------------------------------------------- !
77 ! Initializations
78
80 generic, public :: init => init_from_components
82 procedure, pass(this) :: init_from_components => &
83 design_3dto1d_init_from_components
84
86 procedure, pass(this) :: get_values => design_3dto1d_get_values
87
89 procedure, pass(this) :: update_design => design_3dto1d_update_design
90
92 procedure, pass(this) :: write => design_3dto1d_write
93
95 procedure, pass(this) :: free => design_3dto1d_free
96
97
99 procedure, pass(this) :: map_forward => design_3dto1d_map_forward
101 procedure, pass(this) :: map_backward => design_3dto1d_map_backward
102
103 end type design_3dto1d_t
104
105contains
106
107
108 subroutine design_3dto1d_init_from_components(this, n)
109 class(design_3dto1d_t), intent(inout) :: this
110 integer, intent(in) :: n
111
112 call this%init_base('design_3dto1d', n)
113
114 call this%values%init(n)
115
116 end subroutine design_3dto1d_init_from_components
117
119 subroutine design_3dto1d_free(this)
120 class(design_3dto1d_t), intent(inout) :: this
121
122 call this%free_base()
123 call this%values%free()
124 end subroutine design_3dto1d_free
125
126 subroutine design_3dto1d_map_forward(this)
127 class(design_3dto1d_t), intent(inout) :: this
128
129 end subroutine design_3dto1d_map_forward
130
131 subroutine design_3dto1d_map_backward(this, sensitivity)
132 class(design_3dto1d_t), intent(inout) :: this
133 type(vector_t), intent(in) :: sensitivity
134 end subroutine design_3dto1d_map_backward
135
136
137 subroutine design_3dto1d_get_values(this, values)
138 class(design_3dto1d_t), intent(in) :: this
139 type(vector_t), intent(inout) :: values
140
141 if (this%size() .ne. values%size()) then
142 call neko_error('Get design: size mismatch')
143 end if
144
145 values = this%values
146
147 end subroutine design_3dto1d_get_values
148
149 subroutine design_3dto1d_update_design(this, values)
150 class(design_3dto1d_t), intent(inout) :: this
151 type(vector_t), intent(inout) :: values
152 integer :: n
153
154 n = this%size()
155
156 if (neko_bcknd_device .eq. 1) then
157 call device_copy(this%values%x_d, values%x_d, n)
158 else
159 this%values = values
160 end if
161
162
163 end subroutine design_3dto1d_update_design
164
165 subroutine design_3dto1d_write(this, idx)
166 class(design_3dto1d_t), intent(inout) :: this
167 integer, intent(in) :: idx
168
169 character(len=100) :: filename
170 integer :: i, iunit, ierr
171 real(rp) :: le
172 real(rp), allocatable :: global_values(:)
173 real(rp), allocatable :: global_x(:)
174 integer :: global_size, local_size
175 real(rp) :: l_total
176 integer, allocatable :: recvcounts(:), displs(:)
177 integer :: root_rank = 0
178
179 l_total = 2.0_rp
180
181 ! Get local size on all ranks
182 local_size = this%size()
183
184 ! Only rank 0 handles global arrays
185 if (pe_rank == root_rank) then
186 ! Get global size
187 global_size = this%size_global()
188 allocate(global_values(global_size))
189 allocate(global_x(global_size))
190 allocate(recvcounts(pe_size), displs(pe_size))
191 ! Calculate element length and x positions
192 le = l_total / real(global_size, kind=rp)
193 do i = 1, global_size
194 global_x(i) = le * (i - 0.5_rp) ! Center of each element
195 end do
196 else
197 ! Non-root ranks: minimal dummy allocations
198 allocate(global_values(1), recvcounts(1), displs(1))
199 endif
200
201 ! First, gather all the local sizes to rank 0
202 call mpi_gather(local_size, 1, mpi_integer, &
203 recvcounts, 1, mpi_integer, &
204 root_rank, neko_comm, ierr)
205
206 ! Calculate displacements on rank 0
207 if (pe_rank == root_rank) then
208 displs(1) = 0
209 do i = 2, pe_size
210 displs(i) = displs(i-1) + recvcounts(i-1)
211 end do
212 endif
213
214 if (neko_bcknd_device .eq. 1) then
215 call device_memcpy(this%values%x, this%values%x_d, local_size, &
216 device_to_host, sync = .false.)
217 end if
218 ! Now gather the actual data with proper displacement handling
219 call mpi_gatherv(this%values%x, local_size, mpi_real_precision, &
220 global_values, recvcounts, displs, mpi_real_precision, &
221 root_rank, neko_comm, ierr)
222
223 if (pe_rank == root_rank) then
224 ! Create filename with iteration index
225 write(filename, '(A,I0.6,A)') 'design_iter_', idx, '.txt'
226 ! Open file for writing
227 open(newunit=iunit, file=trim(filename), status='replace', action='write')
228 ! Write header
229 write(iunit, '(A,I0)') '# Iteration: ', idx
230 write(iunit, '(A)') '# x_position height'
231
232 ! Write data
233 do i = 1, global_size
234 write(iunit, '(2E16.8)') global_x(i), global_values(i)
235 end do
236
237 close(iunit)
238
239 deallocate(global_values, global_x, recvcounts, displs)
240 print *, "Design written to ", trim(filename)
241 else
242 deallocate(global_values, recvcounts, displs)
243 endif
244 end subroutine design_3dto1d_write
245
246end module design_3dto1d
Implements the design_t.
Definition design.f90:36
Mappings to be applied to a scalar field.
Definition mapping.f90:36
Some common Masking operations we may need.
Definition mask_ops.f90:36
A PDE based filter.
A RAMP mapping of coefficients.
Implements the steady_problem_t type.
An abstract design type.
Definition design.f90:54
A topology optimization design variable.
Base abstract class for mapping.
Definition mapping.f90:46
A PDE based filter mapping , see Lazarov & O. Sigmund 2010, by solving an equation of the form .
A RAMP mapping of coefficients This is the standard RAMP described in https://doi....