Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_BoundaryDeformation.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: calculate node displacements on those boundaries whose edges
26 ! have moved but which were not marked as moving (finest grid only).
27 !
28 ! Description: none.
29 !
30 ! Input: region = grid dimensions
31 ! boundMoved = flag for boundaries of a region which have moved
32 ! edgeMoved = flag for edges whose nodes have moved
33 ! arcLen12 = arclength between i=const. boundaries for each j, k
34 ! arcLen34 = arclength between j=const. boundaries for each k, i
35 ! arcLen56 = arclength between k=const. boundaries for each i, j
36 ! xyzOld = grid from previous time step.
37 !
38 ! Output: dNode = updated deformations at boundaries.
39 !
40 ! Notes: variable dNode contains the whole 3-D field.
41 !
42 !******************************************************************************
43 !
44 ! $Id: RFLO_BoundaryDeformation.F90,v 1.3 2008/12/06 08:44:06 mtcampbe Exp $
45 !
46 ! Copyright: (c) 2001 by the University of Illinois
47 !
48 !******************************************************************************
49 
50 SUBROUTINE rflo_boundarydeformation( region,boundMoved,edgeMoved, &
51  arclen12,arclen34,arclen56, &
52  xyzold,dnode )
53 
54  USE moddatatypes
55  USE moddatastruct, ONLY : t_region
58  USE moderror
59  USE modparameters
60  IMPLICIT NONE
61 
62 #include "Indexing.h"
63 
64 ! ... parameters
65  LOGICAL :: boundmoved(6), edgemoved(12)
66 
67  REAL(RFREAL), POINTER :: arclen12(:,:), arclen34(:,:), arclen56(:,:)
68  REAL(RFREAL), POINTER :: dnode(:,:), xyzold(:,:)
69 
70  TYPE(t_region) :: region
71 
72 ! ... loop variables
73  INTEGER :: ibound, l1, l2
74 
75 ! ... local variables
76  INTEGER :: ilev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend
77  INTEGER :: l1b, l1e, l2b, l2e, lc, ijkn, ijke(4), ijkem(4), inoff, ijnoff
78  INTEGER :: switch(6,9)
79 
80  LOGICAL :: sum12
81 
82  REAL(RFREAL) :: arclen(4), ds(4), s(4)
83  REAL(RFREAL) :: corner(3,8), e1(3), e2(3), e3(3), e4(3), &
84  p1(3), p2(3), p3(3), p4(3), dn(3)
85 
86 !******************************************************************************
87 
88  CALL registerfunction( region%global,'RFLO_BoundaryDeformation',&
89  'RFLO_BoundaryDeformation.F90' )
90 
91 ! get dimensions --------------------------------------------------------------
92 
93  ilev = 1
94  CALL rflo_getdimensphysnodes( region,ilev,ipnbeg,ipnend, &
95  jpnbeg,jpnend,kpnbeg,kpnend )
96  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
97 
98 ! set boundary switch ---------------------------------------------------------
99 ! switch(:,1-4) = numbers of the 4 edges of a boundary
100 ! switch(:,5-6) = first/last index in l1-direction
101 ! switch(:,7-8) = first/last index in l2-direction
102 ! switch(:, 9) = constant index
103 
104  switch(1,:) = (/ 1, 2, 3, 4, jpnbeg, jpnend, kpnbeg, kpnend, ipnbeg/)
105  switch(2,:) = (/ 5, 6, 7, 8, jpnbeg, jpnend, kpnbeg, kpnend, ipnend/)
106  switch(3,:) = (/ 1, 5, 9, 10, kpnbeg, kpnend, ipnbeg, ipnend, jpnbeg/)
107  switch(4,:) = (/ 3, 7, 11, 12, kpnbeg, kpnend, ipnbeg, ipnend, jpnend/)
108  switch(5,:) = (/ 4, 8, 9, 11, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg/)
109  switch(6,:) = (/ 2, 6, 10, 12, ipnbeg, ipnend, jpnbeg, jpnend, kpnend/)
110 
111 ! store displacements at corners ----------------------------------------------
112 
113  corner(:,1) = dnode(:,indijk(ipnbeg,jpnbeg,kpnbeg,inoff,ijnoff))
114  corner(:,2) = dnode(:,indijk(ipnbeg,jpnbeg,kpnend,inoff,ijnoff))
115  corner(:,3) = dnode(:,indijk(ipnbeg,jpnend,kpnend,inoff,ijnoff))
116  corner(:,4) = dnode(:,indijk(ipnbeg,jpnend,kpnbeg,inoff,ijnoff))
117  corner(:,5) = dnode(:,indijk(ipnend,jpnbeg,kpnbeg,inoff,ijnoff))
118  corner(:,6) = dnode(:,indijk(ipnend,jpnbeg,kpnend,inoff,ijnoff))
119  corner(:,7) = dnode(:,indijk(ipnend,jpnend,kpnend,inoff,ijnoff))
120  corner(:,8) = dnode(:,indijk(ipnend,jpnend,kpnbeg,inoff,ijnoff))
121 
122 ! move nodes on boundaries with active edges ----------------------------------
123 
124  DO ibound=1,6
125  IF ((.NOT.boundmoved(ibound)) .AND. &
126  (edgemoved(switch(ibound,1)) .OR. edgemoved(switch(ibound,2)) .OR. &
127  edgemoved(switch(ibound,3)) .OR. edgemoved(switch(ibound,4)))) THEN
128 
129  l1b = switch(ibound,5)
130  l1e = switch(ibound,6)
131  l2b = switch(ibound,7)
132  l2e = switch(ibound,8)
133  lc = switch(ibound,9)
134 
135  IF (ibound == 1) THEN
136  p1(:) = corner(:,1)
137  p2(:) = corner(:,4)
138  p3(:) = corner(:,3)
139  p4(:) = corner(:,2)
140  ELSE IF (ibound == 2) THEN
141  p1(:) = corner(:,5)
142  p2(:) = corner(:,8)
143  p3(:) = corner(:,7)
144  p4(:) = corner(:,6)
145  ELSE IF (ibound == 3) THEN
146  p1(:) = corner(:,1)
147  p2(:) = corner(:,2)
148  p3(:) = corner(:,6)
149  p4(:) = corner(:,5)
150  ELSE IF (ibound == 4) THEN
151  p1(:) = corner(:,4)
152  p2(:) = corner(:,3)
153  p3(:) = corner(:,7)
154  p4(:) = corner(:,8)
155  ELSE IF (ibound == 5) THEN
156  p1(:) = corner(:,1)
157  p2(:) = corner(:,5)
158  p3(:) = corner(:,8)
159  p4(:) = corner(:,4)
160  ELSE IF (ibound == 6) THEN
161  p1(:) = corner(:,2)
162  p2(:) = corner(:,6)
163  p3(:) = corner(:,7)
164  p4(:) = corner(:,3)
165  ENDIF
166 
167  ds(1:2) = 0._rfreal
168  DO l2=l2b+1,l2e-1
169 
170  sum12 = .true.
171  ds(3:4) = 0._rfreal
172  DO l1=l1b+1,l1e-1
173  IF (ibound==1 .OR. ibound==2) THEN
174  ijkn = indijk(lc,l1 ,l2 ,inoff,ijnoff)
175  ijke(1) = indijk(lc,jpnbeg,l2 ,inoff,ijnoff)
176  ijkem(1) = indijk(lc,jpnbeg,l2-1 ,inoff,ijnoff)
177  ijke(2) = indijk(lc,jpnend,l2 ,inoff,ijnoff)
178  ijkem(2) = indijk(lc,jpnend,l2-1 ,inoff,ijnoff)
179  ijke(3) = indijk(lc,l1 ,kpnbeg,inoff,ijnoff)
180  ijkem(3) = indijk(lc,l1-1 ,kpnbeg,inoff,ijnoff)
181  ijke(4) = indijk(lc,l1 ,kpnend,inoff,ijnoff)
182  ijkem(4) = indijk(lc,l1-1 ,kpnend,inoff,ijnoff)
183  arclen(1) = arclen56(lc,jpnbeg)
184  arclen(2) = arclen56(lc,jpnend)
185  arclen(3) = arclen34(kpnbeg,lc)
186  arclen(4) = arclen34(kpnend,lc)
187  ELSE IF (ibound==3 .OR. ibound==4) THEN
188  ijkn = indijk(l2 ,lc,l1 ,inoff,ijnoff)
189  ijke(1) = indijk(l2 ,lc,kpnbeg,inoff,ijnoff)
190  ijkem(1) = indijk(l2-1 ,lc,kpnbeg,inoff,ijnoff)
191  ijke(2) = indijk(l2 ,lc,kpnend,inoff,ijnoff)
192  ijkem(2) = indijk(l2-1 ,lc,kpnend,inoff,ijnoff)
193  ijke(3) = indijk(ipnbeg,lc,l1 ,inoff,ijnoff)
194  ijkem(3) = indijk(ipnbeg,lc,l1-1 ,inoff,ijnoff)
195  ijke(4) = indijk(ipnend,lc,l1 ,inoff,ijnoff)
196  ijkem(4) = indijk(ipnend,lc,l1-1 ,inoff,ijnoff)
197  arclen(1) = arclen12(lc,kpnbeg)
198  arclen(2) = arclen12(lc,kpnend)
199  arclen(3) = arclen56(ipnbeg,lc)
200  arclen(4) = arclen56(ipnend,lc)
201  ELSE IF (ibound==5 .OR. ibound==6) THEN
202  ijkn = indijk(l1 ,l2 ,lc,inoff,ijnoff)
203  ijke(1) = indijk(ipnbeg,l2 ,lc,inoff,ijnoff)
204  ijkem(1) = indijk(ipnbeg,l2-1 ,lc,inoff,ijnoff)
205  ijke(2) = indijk(ipnend,l2 ,lc,inoff,ijnoff)
206  ijkem(2) = indijk(ipnend,l2-1 ,lc,inoff,ijnoff)
207  ijke(3) = indijk(l1 ,jpnbeg,lc,inoff,ijnoff)
208  ijkem(3) = indijk(l1-1 ,jpnbeg,lc,inoff,ijnoff)
209  ijke(4) = indijk(l1 ,jpnend,lc,inoff,ijnoff)
210  ijkem(4) = indijk(l1-1 ,jpnend,lc,inoff,ijnoff)
211  arclen(1) = arclen34(lc,ipnbeg)
212  arclen(2) = arclen34(lc,ipnend)
213  arclen(3) = arclen12(jpnbeg,lc)
214  arclen(4) = arclen12(jpnend,lc)
215  ENDIF
216  IF (sum12) THEN
217  ds(1) = ds(1) + &
218  sqrt((xyzold(xcoord,ijke(1))-xyzold(xcoord,ijkem(1)))**2 + &
219  (xyzold(ycoord,ijke(1))-xyzold(ycoord,ijkem(1)))**2 + &
220  (xyzold(zcoord,ijke(1))-xyzold(zcoord,ijkem(1)))**2)
221  ds(2) = ds(2) + &
222  sqrt((xyzold(xcoord,ijke(2))-xyzold(xcoord,ijkem(2)))**2 + &
223  (xyzold(ycoord,ijke(2))-xyzold(ycoord,ijkem(2)))**2 + &
224  (xyzold(zcoord,ijke(2))-xyzold(zcoord,ijkem(2)))**2)
225  sum12 = .false.
226  ENDIF
227  ds(3) = ds(3) + &
228  sqrt((xyzold(xcoord,ijke(3))-xyzold(xcoord,ijkem(3)))**2 + &
229  (xyzold(ycoord,ijke(3))-xyzold(ycoord,ijkem(3)))**2 + &
230  (xyzold(zcoord,ijke(3))-xyzold(zcoord,ijkem(3)))**2)
231  ds(4) = ds(4) + &
232  sqrt((xyzold(xcoord,ijke(4))-xyzold(xcoord,ijkem(4)))**2 + &
233  (xyzold(ycoord,ijke(4))-xyzold(ycoord,ijkem(4)))**2 + &
234  (xyzold(zcoord,ijke(4))-xyzold(zcoord,ijkem(4)))**2)
235  s(:) = ds(:)/arclen(:)
236  e1(:) = dnode(:,ijke(1))
237  e2(:) = dnode(:,ijke(2))
238  e3(:) = dnode(:,ijke(3))
239  e4(:) = dnode(:,ijke(4))
240  CALL rflo_tfint2d( s(1),s(2),s(3),s(4),e1,e2,e3,e4,p1,p2,p3,p4,dn )
241  dnode(:,ijkn) = dn(:)
242  ENDDO ! l1
243  ENDDO ! l2
244 
245  ENDIF ! .NOT.boundMoved & edgeMoved
246  ENDDO ! iBound
247 
248 ! finalize --------------------------------------------------------------------
249 
250  CALL deregisterfunction( region%global )
251 
252 END SUBROUTINE rflo_boundarydeformation
253 
254 !******************************************************************************
255 !
256 ! RCS Revision history:
257 !
258 ! $Log: RFLO_BoundaryDeformation.F90,v $
259 ! Revision 1.3 2008/12/06 08:44:06 mtcampbe
260 ! Updated license.
261 !
262 ! Revision 1.2 2008/11/19 22:17:19 mtcampbe
263 ! Added Illinois Open Source License/Copyright
264 !
265 ! Revision 1.1 2004/11/29 21:25:15 wasistho
266 ! lower to upper case
267 !
268 ! Revision 1.8 2003/11/20 16:40:34 mdbrandy
269 ! Backing out RocfluidMP changes from 11-17-03
270 !
271 ! Revision 1.5 2003/05/15 02:57:01 jblazek
272 ! Inlined index function.
273 !
274 ! Revision 1.4 2003/05/06 20:05:38 jblazek
275 ! Corrected bug in grid motion (corner "averaging").
276 !
277 ! Revision 1.3 2003/03/14 22:05:10 jblazek
278 ! Improved mesh motion algorithm - node movement exchaged between blocks.
279 !
280 ! Revision 1.2 2002/09/05 17:40:19 jblazek
281 ! Variable global moved into regions().
282 !
283 ! Revision 1.1 2002/08/15 19:48:04 jblazek
284 ! Implemented grid deformation capability.
285 !
286 !******************************************************************************
287 
288 
289 
290 
291 
292 
293 
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jpnbeg
double s
Definition: blastest.C:80
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE kpnbeg
NT p1
subroutine rflo_tfint2d(s1, s2, s3, s4, e1, e2, e3, e4, p1, p2, p3, p4, xyz)
Definition: RFLO_Tfint.F90:76
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
double sqrt(double d)
Definition: double.h:73
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jpnend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ipnbeg
subroutine rflo_getdimensphysnodes(region, iLev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend)
subroutine rflo_boundarydeformation(region, boundMoved, edgeMoved, arcLen12, arcLen34, arcLen56, xyzOld, dNode)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ipnend