Neko  0.8.1
A portable framework for high-order spectral element flow simulations
drag_torque.f90
Go to the documentation of this file.
1 ! Copyright (c) 2008-2020, UCHICAGO ARGONNE, LLC.
2 !
3 ! The UChicago Argonne, LLC as Operator of Argonne National
4 ! Laboratory holds copyright in the Software. The copyright holder
5 ! reserves all rights except those expressly granted to licensees,
6 ! and U.S. Government license rights.
7 !
8 ! Redistribution and use in source and binary forms, with or without
9 ! modification, are permitted provided that the following conditions
10 ! are met:
11 !
12 ! 1. Redistributions of source code must retain the above copyright
13 ! notice, this list of conditions and the disclaimer below.
14 !
15 ! 2. Redistributions in binary form must reproduce the above copyright
16 ! notice, this list of conditions and the disclaimer (as noted below)
17 ! in the documentation and/or other materials provided with the
18 ! distribution.
19 !
20 ! 3. Neither the name of ANL nor the names of its contributors
21 ! may be used to endorse or promote products derived from this software
22 ! without specific prior written permission.
23 !
24 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
25 ! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
26 ! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
27 ! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL
28 ! UCHICAGO ARGONNE, LLC, THE U.S. DEPARTMENT OF
29 ! ENERGY OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
30 ! SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED
31 ! TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
32 ! DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
33 ! THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
34 ! (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
35 ! OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
36 !
37 ! Additional BSD Notice
38 ! ---------------------
39 ! 1. This notice is required to be provided under our contract with
40 ! the U.S. Department of Energy (DOE). This work was produced at
41 ! Argonne National Laboratory under Contract
42 ! No. DE-AC02-06CH11357 with the DOE.
43 !
44 ! 2. Neither the United States Government nor UCHICAGO ARGONNE,
45 ! LLC nor any of their employees, makes any warranty,
46 ! express or implied, or assumes any liability or responsibility for the
47 ! accuracy, completeness, or usefulness of any information, apparatus,
48 ! product, or process disclosed, or represents that its use would not
49 ! infringe privately-owned rights.
50 !
51 ! 3. Also, reference herein to any specific commercial products, process,
52 ! or services by trade name, trademark, manufacturer or otherwise does
53 ! not necessarily constitute or imply its endorsement, recommendation,
54 ! or favoring by the United States Government or UCHICAGO ARGONNE LLC.
55 ! The views and opinions of authors expressed
56 ! herein do not necessarily state or reflect those of the United States
57 ! Government or UCHICAGO ARGONNE, LLC, and shall
58 ! not be used for advertising or product endorsement purposes.
59 !
60 
62  use field, only: field_t
63  use coefs, only: coef_t
64  use mesh
65  use facet_zone
66  use comm
67  use math
68  use space, only: space_t
69  use num_types, only: rp
70  use operators
71  implicit none
72  private
77 
78 contains
88  subroutine drag_torque_zone(dgtq, tstep, zone, center, s11, s22, s33, s12, s13, s23,&
89  p, coef, visc)
90  integer, intent(in) :: tstep
91  type(facet_zone_t) :: zone
92  type(coef_t), intent(inout) :: coef
93  real(kind=rp), intent(inout) :: s11(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
94  real(kind=rp), intent(inout) :: s22(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
95  real(kind=rp), intent(inout) :: s33(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
96  real(kind=rp), intent(inout) :: s12(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
97  real(kind=rp), intent(inout) :: s13(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
98  real(kind=rp), intent(inout) :: s23(coef%Xh%lx,coef%Xh%lx,coef%Xh%lz,coef%msh%nelv)
99  type(field_t), intent(inout) :: p
100  real(kind=rp), intent(in) :: visc, center(3)
101  real(kind=rp) :: dgtq(3,4)
102  real(kind=rp) :: dragpx = 0.0_rp ! pressure
103  real(kind=rp) :: dragpy = 0.0_rp
104  real(kind=rp) :: dragpz = 0.0_rp
105  real(kind=rp) :: dragvx = 0.0_rp ! viscous
106  real(kind=rp) :: dragvy = 0.0_rp
107  real(kind=rp) :: dragvz = 0.0_rp
108  real(kind=rp) :: torqpx = 0.0_rp ! pressure
109  real(kind=rp) :: torqpy = 0.0_rp
110  real(kind=rp) :: torqpz = 0.0_rp
111  real(kind=rp) :: torqvx = 0.0_rp ! viscous
112  real(kind=rp) :: torqvy = 0.0_rp
113  real(kind=rp) :: torqvz = 0.0_rp
114  real(kind=rp) :: dragx, dragy, dragz
115  real(kind=rp) :: torqx, torqy, torqz
116  integer :: ie, ifc, mem, ierr
117  dragx = 0.0
118  dragy = 0.0
119  dragz = 0.0
120 
121 !
122 ! Fill up viscous array w/ default
123 !
124  dragpx = 0.0
125  dragpy = 0.0
126  dragpz = 0.0
127  dragvx = 0.0
128  dragvy = 0.0
129  dragvz = 0.0
130  do mem = 1,zone%size
131  ie = zone%facet_el(mem)%x(2)
132  ifc = zone%facet_el(mem)%x(1)
133  call drag_torque_facet(dgtq,coef%dof%x,coef%dof%y,coef%dof%z,&
134  center,&
135  s11, s22, s33, s12, s13, s23,&
136  p%x,visc,ifc,ie, coef, coef%Xh)
137 
138  dragpx = dragpx + dgtq(1,1) ! pressure
139  dragpy = dragpy + dgtq(2,1)
140  dragpz = dragpz + dgtq(3,1)
141 
142  dragvx = dragvx + dgtq(1,2) ! viscous
143  dragvy = dragvy + dgtq(2,2)
144  dragvz = dragvz + dgtq(3,2)
145 
146  torqpx = torqpx + dgtq(1,3) ! pressure
147  torqpy = torqpy + dgtq(2,3)
148  torqpz = torqpz + dgtq(3,3)
149 
150  torqvx = torqvx + dgtq(1,4) ! viscous
151  torqvy = torqvy + dgtq(2,4)
152  torqvz = torqvz + dgtq(3,4)
153  enddo
154 !
155 ! Sum contributions from all processors
156 !
157  call mpi_allreduce(mpi_in_place,dragpx, 1, &
158  mpi_real_precision, mpi_sum, neko_comm, ierr)
159  call mpi_allreduce(mpi_in_place,dragpy, 1, &
160  mpi_real_precision, mpi_sum, neko_comm, ierr)
161  call mpi_allreduce(mpi_in_place,dragpz, 1, &
162  mpi_real_precision, mpi_sum, neko_comm, ierr)
163  call mpi_allreduce(mpi_in_place,dragvx, 1, &
164  mpi_real_precision, mpi_sum, neko_comm, ierr)
165  call mpi_allreduce(mpi_in_place,dragvy, 1, &
166  mpi_real_precision, mpi_sum, neko_comm, ierr)
167  call mpi_allreduce(mpi_in_place,dragvz, 1, &
168  mpi_real_precision, mpi_sum, neko_comm, ierr)
169  !Torque
170  call mpi_allreduce(mpi_in_place,torqpx, 1, &
171  mpi_real_precision, mpi_sum, neko_comm, ierr)
172  call mpi_allreduce(mpi_in_place,torqpy, 1, &
173  mpi_real_precision, mpi_sum, neko_comm, ierr)
174  call mpi_allreduce(mpi_in_place,torqpz, 1, &
175  mpi_real_precision, mpi_sum, neko_comm, ierr)
176  call mpi_allreduce(mpi_in_place,torqvx, 1, &
177  mpi_real_precision, mpi_sum, neko_comm, ierr)
178  call mpi_allreduce(mpi_in_place,torqvy, 1, &
179  mpi_real_precision, mpi_sum, neko_comm, ierr)
180  call mpi_allreduce(mpi_in_place,torqvz, 1, &
181  mpi_real_precision, mpi_sum, neko_comm, ierr)
182 
183  dgtq(1,1) = dragpx ! pressure
184  dgtq(2,1) = dragpy
185  dgtq(3,1) = dragpz
186 
187  dgtq(1,2) = dragvx ! viscous
188  dgtq(2,2) = dragvy
189  dgtq(3,2) = dragvz
190 
191  dgtq(1,3) = torqpx ! pressure
192  dgtq(2,3) = torqpy
193  dgtq(3,3) = torqpz
194 
195  dgtq(1,4) = torqvx ! viscous
196  dgtq(2,4) = torqvy
197  dgtq(3,4) = torqvz
198 
199  end subroutine drag_torque_zone
200 
212  subroutine drag_torque_facet(dgtq,xm0,ym0,zm0, center,&
213  s11, s22, s33, s12, s13, s23,&
214  pm1,visc,f,e, coef, Xh)
215  type(coef_t), intent(in) :: coef
216  type(space_t), intent(in) :: xh
217  real(kind=rp), intent(out) :: dgtq(3,4)
218  real(kind=rp), intent(in) :: center(3)
219  real(kind=rp), intent(in) :: xm0(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
220  real(kind=rp), intent(in) :: ym0(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
221  real(kind=rp), intent(in) :: zm0(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
222  real(kind=rp), intent(in) :: s11(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
223  real(kind=rp), intent(in) :: s22(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
224  real(kind=rp), intent(in) :: s33(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
225  real(kind=rp), intent(in) :: s12(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
226  real(kind=rp), intent(in) :: s13(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
227  real(kind=rp), intent(in) :: s23(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
228  real(kind=rp), intent(in) :: pm1(xh%lx,xh%ly,xh%lz,coef%msh%nelv)
229  real(kind=rp), intent(in) :: visc
230  integer, intent(in) :: f,e
231  integer :: pf,l, k, i, j1, j2
232  real(kind=rp) :: n1,n2,n3, j, a, r1, r2, r3, v, dgtq_i(3,4)
233  integer :: skpdat(6,6), nx, ny, nz
234  integer :: js1
235  integer :: jf1
236  integer :: jskip1
237  integer :: js2
238  integer :: jf2
239  integer :: jskip2
240  real(kind=rp) :: s11_, s21_, s31_, s12_, s22_, s32_, s13_, s23_, s33_
241 
242 
243  nx = xh%lx
244  ny = xh%ly
245  nz = xh%lz
246  skpdat(1,1)=1
247  skpdat(2,1)=nx*(ny-1)+1
248  skpdat(3,1)=nx
249  skpdat(4,1)=1
250  skpdat(5,1)=ny*(nz-1)+1
251  skpdat(6,1)=ny
252 
253  skpdat(1,2)=1 + (nx-1)
254  skpdat(2,2)=nx*(ny-1)+1 + (nx-1)
255  skpdat(3,2)=nx
256  skpdat(4,2)=1
257  skpdat(5,2)=ny*(nz-1)+1
258  skpdat(6,2)=ny
259 
260  skpdat(1,3)=1
261  skpdat(2,3)=nx
262  skpdat(3,3)=1
263  skpdat(4,3)=1
264  skpdat(5,3)=ny*(nz-1)+1
265  skpdat(6,3)=ny
266 
267  skpdat(1,4)=1 + nx*(ny-1)
268  skpdat(2,4)=nx + nx*(ny-1)
269  skpdat(3,4)=1
270  skpdat(4,4)=1
271  skpdat(5,4)=ny*(nz-1)+1
272  skpdat(6,4)=ny
273 
274  skpdat(1,5)=1
275  skpdat(2,5)=nx
276  skpdat(3,5)=1
277  skpdat(4,5)=1
278  skpdat(5,5)=ny
279  skpdat(6,5)=1
280 
281  skpdat(1,6)=1 + nx*ny*(nz-1)
282  skpdat(2,6)=nx + nx*ny*(nz-1)
283  skpdat(3,6)=1
284  skpdat(4,6)=1
285  skpdat(5,6)=ny
286  skpdat(6,6)=1
287  pf = f
288  js1 = skpdat(1,pf)
289  jf1 = skpdat(2,pf)
290  jskip1 = skpdat(3,pf)
291  js2 = skpdat(4,pf)
292  jf2 = skpdat(5,pf)
293  jskip2 = skpdat(6,pf)
294  call rzero(dgtq,12)
295  i = 0
296  a = 0
297  do j2=js2,jf2,jskip2
298  do j1=js1,jf1,jskip1
299  i = i+1
300  n1 = coef%nx(i,1,f,e)*coef%area(i,1,f,e)
301  n2 = coef%ny(i,1,f,e)*coef%area(i,1,f,e)
302  n3 = coef%nz(i,1,f,e)*coef%area(i,1,f,e)
303  a = a + coef%area(i,1,f,e)
304  v = visc
305  s11_ = s11(j1,j2,1,e)
306  s12_ = s12(j1,j2,1,e)
307  s22_ = s22(j1,j2,1,e)
308  s13_ = s13(j1,j2,1,e)
309  s23_ = s23(j1,j2,1,e)
310  s33_ = s33(j1,j2,1,e)
311  call drag_torque_pt(dgtq_i,xm0(j1,j2,1,e), ym0(j1,j2,1,e),zm0(j1,j2,1,e), center,&
312  s11_, s22_, s33_, s12_, s13_, s23_,&
313  pm1(j1,j2,1,e), n1, n2, n3, v)
314  dgtq = dgtq + dgtq_i
315  end do
316  end do
317  end subroutine drag_torque_facet
318 
331  subroutine drag_torque_pt(dgtq,x,y,z, center, s11, s22, s33, s12, s13, s23,&
332  p,n1, n2, n3,v)
333  real(kind=rp), intent(inout) :: dgtq(3,4)
334  real(kind=rp), intent(in) :: x
335  real(kind=rp), intent(in) :: y
336  real(kind=rp), intent(in) :: z
337  real(kind=rp), intent(in) :: p
338  real(kind=rp), intent(in) :: v
339  real(kind=rp), intent(in) :: n1, n2, n3, center(3)
340  real(kind=rp), intent(in) :: s11, s12, s22, s13, s23, s33
341  real(kind=rp) :: s21, s31, s32, r1, r2, r3
342  call rzero(dgtq,12)
343  s21 = s12
344  s32 = s23
345  s31 = s13
346  !pressure drag
347  dgtq(1,1) = p*n1
348  dgtq(2,1) = p*n2
349  dgtq(3,1) = p*n3
350  ! viscous drag
351  dgtq(1,2) = -v*(s11*n1 + s12*n2 + s13*n3)
352  dgtq(2,2) = -v*(s21*n1 + s22*n2 + s23*n3)
353  dgtq(3,2) = -v*(s31*n1 + s32*n2 + s33*n3)
354  r1 = x-center(1)
355  r2 = y-center(2)
356  r3 = z-center(3)
357  !pressure torque
358  dgtq(1,3) = (r2*dgtq(3,1)-r3*dgtq(2,1))
359  dgtq(2,3) = (r3*dgtq(1,1)-r1*dgtq(3,1))
360  dgtq(3,3) = (r1*dgtq(2,1)-r2*dgtq(1,1))
361  !viscous torque
362  dgtq(1,4) = (r2*dgtq(3,2)-r3*dgtq(2,2))
363  dgtq(2,4) = (r3*dgtq(1,2)-r1*dgtq(3,2))
364  dgtq(3,4) = (r1*dgtq(2,2)-r2*dgtq(1,2))
365  end subroutine drag_torque_pt
366 
367 end module drag_torque
Coefficients.
Definition: coef.f90:34
Definition: comm.F90:1
type(mpi_comm) neko_comm
MPI communicator.
Definition: comm.F90:16
type(mpi_datatype) mpi_real_precision
MPI type for working precision of REAL types.
Definition: comm.F90:22
subroutine, public drag_torque_zone(dgtq, tstep, zone, center, s11, s22, s33, s12, s13, s23, p, coef, visc)
Some functions to calculate the lift/drag and torque Calculation can be done on a zone,...
Definition: drag_torque.f90:90
subroutine, public drag_torque_facet(dgtq, xm0, ym0, zm0, center, s11, s22, s33, s12, s13, s23, pm1, visc, f, e, coef, Xh)
Calculate drag and torque over a facet.
subroutine, public drag_torque_pt(dgtq, x, y, z, center, s11, s22, s33, s12, s13, s23, p, n1, n2, n3, v)
Calculate drag and torque from one point.
Defines a zone as a subset of facets in a mesh.
Definition: facet_zone.f90:34
Defines a field.
Definition: field.f90:34
Definition: math.f90:60
subroutine, public rzero(a, n)
Zero a real vector.
Definition: math.f90:167
Defines a mesh.
Definition: mesh.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Operators.
Definition: operators.f90:34
Defines a function space.
Definition: space.f90:34
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:54
The function space for the SEM solution fields.
Definition: space.f90:62