Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
UpdateStructuralSoln.f90
Go to the documentation of this file.
1 !*********************************************************************
2 !* Illinois Open Source License *
3 !* *
4 !* University of Illinois/NCSA *
5 !* Open Source License *
6 !* *
7 !* Copyright@2008, University of Illinois. All rights reserved. *
8 !* *
9 !* Developed by: *
10 !* *
11 !* Center for Simulation of Advanced Rockets *
12 !* *
13 !* University of Illinois *
14 !* *
15 !* www.csar.uiuc.edu *
16 !* *
17 !* Permission is hereby granted, free of charge, to any person *
18 !* obtaining a copy of this software and associated documentation *
19 !* files (the "Software"), to deal with the Software without *
20 !* restriction, including without limitation the rights to use, *
21 !* copy, modify, merge, publish, distribute, sublicense, and/or *
22 !* sell copies of the Software, and to permit persons to whom the *
23 !* Software is furnished to do so, subject to the following *
24 !* conditions: *
25 !* *
26 !* *
27 !* @ Redistributions of source code must retain the above copyright *
28 !* notice, this list of conditions and the following disclaimers. *
29 !* *
30 !* @ Redistributions in binary form must reproduce the above *
31 !* copyright notice, this list of conditions and the following *
32 !* disclaimers in the documentation and/or other materials *
33 !* provided with the distribution. *
34 !* *
35 !* @ Neither the names of the Center for Simulation of Advanced *
36 !* Rockets, the University of Illinois, nor the names of its *
37 !* contributors may be used to endorse or promote products derived *
38 !* from this Software without specific prior written permission. *
39 !* *
40 !* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
41 !* EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
42 !* OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
43 !* NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
44 !* COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
45 !* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
46 !* ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
47 !* USE OR OTHER DEALINGS WITH THE SOFTWARE. *
48 !*********************************************************************
49 !* Please acknowledge The University of Illinois Center for *
50 !* Simulation of Advanced Rockets in works and publications *
51 !* resulting from this software or its derivatives. *
52 !*********************************************************************
53 
55 
56  USE rocstar_rocfrac
58 
59 CONTAINS
60 
61  SUBROUTINE updatestructural(glb,NumProcs,Rnet)
62 
63  IMPLICIT NONE
64 
65  include 'mpif.h'
66 
67  TYPE(rocfrac_global) :: glb
68 
69  INTEGER :: numnp ! Number of Node Points
70  INTEGER :: numelvol ! Number of Volumetric Elements
71  INTEGER :: nummatvol ! Number of Volumetreic Materials
72  INTEGER :: nummatcoh ! Number of Cohesive Materials
73  INTEGER :: numprocs ! Number of processors
74  INTEGER :: ieltype ! Order of element (4:4node, 5:4nodeEnhanced, 10:10node)
75  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
76  REAL*8, POINTER, DIMENSION(:,:) :: meshcoor
77  INTEGER, POINTER, DIMENSION(:) :: matidvol
78  INTEGER, POINTER, DIMENSION(:,:) :: elconnvol
79  REAL*8, POINTER, DIMENSION(:) :: e, xnu, rho
80  REAL*8, POINTER, DIMENSION(:) :: disp ! Nodal Displacement
81  REAL*8, POINTER, DIMENSION(:) :: deltan, deltat
82  REAL*8, POINTER, DIMENSION(:) :: velohalf ! velocity
83  REAL*8, POINTER, DIMENSION(:) :: velobar, accelbar
84  REAL*8 :: kappadamp
85  LOGICAL :: aleenabled, dampenabled
86  INTEGER, POINTER, DIMENSION(:) :: isolntype
87 ! LOGICAL :: DefConfig
88  INTEGER :: totnumneighprocs
89  INTEGER :: mpi_comm_rocfrac
90 !-- Non-block receive, Non-block send request arrays
91  INTEGER, POINTER, DIMENSION(:) :: reqrcv, reqsnd
92  INTEGER, POINTER, DIMENSION(:,:) :: statrcv, statsnd
93  INTEGER :: totnumndcomm
94 
95  INTEGER :: numelpartbndry
96  INTEGER, DIMENSION(:), POINTER :: numelpartbndrymat
97  INTEGER, DIMENSION(:), POINTER :: neighproclist
98  INTEGER, DIMENSION(:), POINTER :: numndcomm
99  INTEGER, DIMENSION(:), POINTER :: numelvolmat
100 
101  TYPE(send_buf), DIMENSION(:), POINTER :: ndcommlist
102 
103  TYPE(rcv_buf), DIMENSION(:), POINTER :: recvdatafrm
104 
105  TYPE(send_buf), POINTER :: pndcomm
106  TYPE(rcv_buf), POINTER :: precvdf
107 
108  REAL*8, ALLOCATABLE, DIMENSION(:) :: buf
109 
110  INTEGER :: j, j1, k , k1, k2
111  INTEGER :: ierr,ianalysistype
112  INTEGER :: elemstart, elemend
113  REAL*8, POINTER, DIMENSION(:) :: sigmamax, taumax, sinit
114  REAL*8, POINTER, DIMENSION(:,:) :: sthresh1 ,sthresh2
115 
116 !------ CALCULATE THE SUBMESH'S BOUNDARY INTERNAL FORCE VECTOR
117 
118 
119  numnp = glb%NumNP
120  numelvol = glb%NumElVol
121  nummatvol = glb%NumMatVol
122  nummatcoh = glb%NumMatCoh
123  ieltype = glb%iEltype
124 
125 ! Rnet => glb%Rnet
126  meshcoor => glb%MeshCoor
127  matidvol => glb%MatIdVol
128  elconnvol => glb%ElConnVol
129  disp => glb%Disp
130  deltan => glb%deltan
131  deltat => glb%deltat
132  sigmamax => glb%SigmaMax
133  taumax => glb%TauMax
134  sthresh1 => glb%Sthresh1
135  sthresh2 => glb%Sthresh2
136  sinit => glb%Sinit
137  velohalf => glb%VeloHalf
138  velobar => glb%VeloBar
139  accelbar => glb%AccelBar
140  kappadamp = glb%KappaDamp
141  aleenabled = glb%ALEenabled
142  dampenabled = glb%DampEnabled
143  isolntype => glb%iSolnType
144 ! DefConfig = glb%DefConfig
145  totnumneighprocs = glb%TotNumNeighProcs
146  mpi_comm_rocfrac = glb%MPI_COMM_ROCFRAC
147  reqrcv => glb%ReqRcv
148  reqsnd => glb%ReqSnd
149  statrcv => glb%StatRcv
150  statsnd => glb%StatSnd
151  totnumndcomm = glb%TotNumNdComm
152  numelpartbndry = glb%NumElPartBndry
153  numelpartbndrymat => glb%NumElPartBndryMat
154  neighproclist => glb%NeighProcList
155  numndcomm => glb%NumNdComm
156  numelvolmat => glb%NumElVolMat
157  ndcommlist => glb%NdCommList
158  recvdatafrm => glb%RecvDataFrm
159  e => glb%E
160  xnu => glb%xnu
161  rho => glb%rho
162 
163  elemstart = 1
164 
165  DO j = 1, nummatvol
166 
167  elemend = numelpartbndrymat(j) + elemstart - 1
168 
169  ianalysistype = isolntype(j)
170 
171  IF(ieltype.EQ.4)THEN
172  CALL internalforce_v3d4( glb, rnet, elemstart, elemend, ianalysistype)
173  ELSE IF(ieltype.EQ.10)THEN
174  CALL internalforce_v3d10( glb, rnet, elemstart, elemend, ianalysistype)
175  ELSE IF(ieltype.EQ.8)THEN
176  CALL internalforce_v3d8( glb, rnet, elemstart, elemend, ianalysistype)
177  ENDIF
178 
179  elemstart = numelvolmat(j) + elemstart
180  ENDDO
181 
182  DO j = 1, nummatcoh
183 
184  ! Transfer the cohesive solution to the 'Top' Surface
185 
186  CALL c3d6nm( glb%nsubn1, glb%nsubf1, &
187  glb%nsubn2, glb%nsubf2, &
188  glb%sd_coor1, glb%sd_subfaces1, &
189  glb%sd_subface_parents1, &
190  glb%sd_subface_parents2, &
191  glb%sd_subface_counterparts1, &
192  glb%sd_subface_nat_coors1, &
193  glb%sd_subface_nat_coors2, &
194  glb%FaceOfVolEl1, &
195  glb%FaceOfVolEl2, &
196  glb%NumNp, glb%NumElVol, &
197  glb%ElConnVol, &
198  glb%nf1,glb%nf2, &
199  glb%MapFaceEl2Vol1, &
200  glb%MapFaceEl2Vol2, &
201  deltan, deltat, sigmamax, taumax, sinit, &
202  rnet, disp, sthresh1, glb%NumMatCoh,j,-1.d0)
203 
204  ! Transfer the cohesive solution to the 'Bottom' Surface
205 
206 !!$ CALL c3d6nm( glb%nsubn2, glb%nsubf2, &
207 !!$ glb%sd_coor2, glb%sd_subfaces2, &
208 !!$ glb%sd_subface_parents2, &
209 !!$ glb%sd_subface_counterparts2, &
210 !!$ glb%sd_subface_nat_coors2, &
211 !!$ glb%FaceOfVolEl2, &
212 !!$ glb%NumNp, glb%NumElVol, &
213 !!$ glb%ElConnVol, &
214 !!$ glb%nf2, &
215 !!$ glb%MapFaceEl2Vol2, &
216 !!$ deltan, deltat, SigmaMax, TauMax, Sinit, &
217 !!$ Rnet, Disp, Sthresh1, glb%NumMatCoh,j,1.d0)
218 
219 
220  ENDDO
221 
222 !
223 !----- FORM THE BUFFER CONTAINING COMMUNICATED NODAL VALUES
224 !
225  ALLOCATE(buf(1:totnumndcomm))
226  k1 = 1
227  DO j1 = 1, totnumneighprocs
228  k = neighproclist(j1)
229  pndcomm => ndcommlist(j1)
230  DO j = 1, numndcomm(j1)
231  k2 = 3*pndcomm%NdId(j)
232  buf(k1) = rnet( k2 - 2 )
233  buf(k1+1) = rnet( k2 - 1 )
234  buf(k1+2) = rnet( k2 )
235  k1 = k1 + 3
236  ENDDO
237  ENDDO
238 
239 !
240 !-MPI- RECEIVE THE INTERNAL FORCE VECTOR FROM THE NEIGHBORS
241 !
242  DO j1 = 1, totnumneighprocs
243  k = neighproclist(j1)+1
244  CALL mpi_irecv(recvdatafrm(k)%rcvbuf(1),numndcomm(j1)*3, &
245  mpi_double_precision,k-1,10,mpi_comm_rocfrac, &
246  reqrcv(j1),ierr)
247  ENDDO
248 !
249 !-MPI- SEND THE INTERNAL FORCE VECTOR TO THE NEIGHBORS
250 !
251  k2 = 1
252  DO j1 = 1, totnumneighprocs
253  k = neighproclist(j1)
254  CALL mpi_isend(buf(k2), numndcomm(j1)*3,mpi_double_precision, &
255  k,10,mpi_comm_rocfrac,reqsnd(j1),ierr)
256  k2 = k2 + numndcomm(j1)*3
257  ENDDO
258 
259 !
260 !-MPI- WAIT FOR INTERNAL FORCE VECTOR COMMUNICATION TO COMPLETE
261 !
262 
263  IF(aleenabled)THEN
264  IF(ieltype.EQ.4)THEN
265  CALL v3d4_ale(velobar,accelbar,disp,velohalf,rnet, &
266  e,xnu,rho,numnp,nummatvol, &
267  numelvol,matidvol,elconnvol,meshcoor, &
268  numelpartbndry+1,numelvol)
269  ELSE
270  CALL v3d10_ale(velobar,accelbar,disp,velohalf,rnet, &
271  e,xnu,rho,numnp,nummatvol, &
272  numelvol,matidvol,elconnvol,meshcoor, &
273  numelpartbndry+1,numelvol)
274  ENDIF
275  ENDIF
276 
277 !-- (11) calculate R_in, R_damp
278 
279 !------ CALCULATE THE SUBMESH'S BOUNDARY INTERNAL FORCE VECTOR
280 
281  elemend = 0
282  DO j = 1, nummatvol
283 
284  elemstart = elemend + numelpartbndrymat(j) + 1
285 
286  elemend = numelvolmat(j) + elemend
287 
288  IF(ieltype.EQ.4)THEN
289  CALL internalforce_v3d4( glb, rnet, elemstart, elemend, ianalysistype)
290  ELSE IF(ieltype.EQ.10)THEN
291  CALL internalforce_v3d10( glb, rnet, elemstart, elemend, ianalysistype)
292  ELSE IF(ieltype.EQ.8)THEN
293  CALL internalforce_v3d8( glb, rnet, elemstart, elemend, ianalysistype)
294  ENDIF
295  ENDDO
296 
297  IF(totnumneighprocs.GT.0)THEN
298  CALL mpi_waitall(totnumneighprocs,reqrcv,statrcv,ierr)
299  CALL mpi_waitall(totnumneighprocs,reqsnd,statsnd,ierr)
300  ENDIF
301 
302  DEALLOCATE(buf)
303 
304 !
305 !----- ADD NEIGHBOR'S CONTRIBUTION TO THE INTERNAL FORCE VECTOR
306 !
307  DO j1 = 1, totnumneighprocs
308  k = neighproclist(j1)+1
309  k1 = 1
310  pndcomm => ndcommlist(j1)
311  precvdf => recvdatafrm(k)
312  DO j = 1, numndcomm(j1)
313  k2 = ( pndcomm%NdId(j) )*3
314  rnet(k2-2)= rnet(k2-2) + precvdf%rcvbuf(k1)
315  rnet(k2-1)= rnet(k2-1) + precvdf%rcvbuf(k1+1)
316  rnet(k2) = rnet(k2) + precvdf%rcvbuf(k1+2)
317  k1 = k1 + 3
318  ENDDO
319  ENDDO
320 
321  RETURN
322  END SUBROUTINE updatestructural
323 
324  SUBROUTINE updatestructuralht(glb,NumProcs,Rnet,RnetHT)
325 
326  IMPLICIT NONE
327 
328  include 'mpif.h'
329 
330  TYPE(rocfrac_global) :: glb
331 
332  INTEGER :: numnp ! Number of Node Points
333  INTEGER :: numelvol ! Number of Volumetric Elements
334  INTEGER :: nummatvol ! Number of Volumetreic Materials
335  INTEGER :: numprocs ! Number of processors
336  INTEGER :: ieltype ! Order of element (4:4node, 5:4nodeEnhanced, 10:10node)
337  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
338  REAL*8, DIMENSION(1:glb%NumNP) :: rnetht
339  REAL*8, POINTER, DIMENSION(:,:) :: meshcoor
340  INTEGER, POINTER, DIMENSION(:) :: matidvol
341  INTEGER, POINTER, DIMENSION(:,:) :: elconnvol
342  REAL*8, POINTER, DIMENSION(:) :: e, xnu, rho, cp, kappaht
343  REAL*8, POINTER, DIMENSION(:) :: disp ! Nodal Displacement
344  REAL*8, POINTER, DIMENSION(:) :: velohalf ! velocity
345  REAL*8, POINTER, DIMENSION(:) :: velobar, accelbar
346  REAL*8 :: kappadamp
347  LOGICAL :: aleenabled, dampenabled
348  INTEGER, POINTER, DIMENSION(:) :: isolntype
349 ! LOGICAL :: DefConfig
350  INTEGER :: totnumneighprocs
351  INTEGER :: mpi_comm_rocfrac
352 !-- Non-block receive, Non-block send request arrays
353  INTEGER, POINTER, DIMENSION(:) :: reqrcv, reqsnd
354  INTEGER, POINTER, DIMENSION(:,:) :: statrcv, statsnd
355  INTEGER :: totnumndcomm
356 
357  INTEGER :: numelpartbndry
358  INTEGER, DIMENSION(:), POINTER :: numelpartbndrymat
359  INTEGER, DIMENSION(:), POINTER :: neighproclist
360  INTEGER, DIMENSION(:), POINTER :: numndcomm
361  INTEGER, DIMENSION(:), POINTER :: numelvolmat
362 
363  integer :: k4
364 
365  TYPE(send_buf), DIMENSION(:), POINTER :: ndcommlist
366 
367  TYPE(rcv_buf), DIMENSION(:), POINTER :: recvdatafrm
368 
369  TYPE(send_buf), POINTER :: pndcomm
370  TYPE(rcv_buf), POINTER :: precvdf
371 
372  REAL*8, ALLOCATABLE, DIMENSION(:) :: buf
373 
374  INTEGER :: i, j, j1, k , k1, k2
375  INTEGER :: ierr,ianalysistype
376  INTEGER :: elemstart, elemend
377  logical :: heattranssoln
378 
379  integer :: numndsbcht
380  real*8, DIMENSION(:), POINTER :: temperature
381  integer, DIMENSION(:,:), POINTER :: bcflaght
382  real*8, DIMENSION(:,:), POINTER :: bcvalueht
383 
384 !------ CALCULATE THE SUBMESH'S BOUNDARY INTERNAL FORCE VECTOR
385 
386 
387  numnp = glb%NumNP
388  numelvol = glb%NumElVol
389  nummatvol = glb%NumMatVol
390  ieltype = glb%iEltype
391 
392 ! Rnet => glb%Rnet
393  meshcoor => glb%MeshCoor
394  matidvol => glb%MatIdVol
395  elconnvol => glb%ElConnVol
396  disp => glb%Disp
397  velohalf => glb%VeloHalf
398  velobar => glb%VeloBar
399  accelbar => glb%AccelBar
400  kappadamp = glb%KappaDamp
401  aleenabled = glb%ALEenabled
402  dampenabled = glb%DampEnabled
403  isolntype => glb%iSolnType
404 ! DefConfig = glb%DefConfig
405  totnumneighprocs = glb%TotNumNeighProcs
406  mpi_comm_rocfrac = glb%MPI_COMM_ROCFRAC
407  reqrcv => glb%ReqRcv
408  reqsnd => glb%ReqSnd
409  statrcv => glb%StatRcv
410  statsnd => glb%StatSnd
411  totnumndcomm = glb%TotNumNdComm
412  numelpartbndry = glb%NumElPartBndry
413  numelpartbndrymat => glb%NumElPartBndryMat
414  neighproclist => glb%NeighProcList
415  numndcomm => glb%NumNdComm
416  numelvolmat => glb%NumElVolMat
417  ndcommlist => glb%NdCommList
418  recvdatafrm => glb%RecvDataFrm
419  e => glb%E
420  xnu => glb%xnu
421  rho => glb%rho
422  cp => glb%Cp
423  kappaht => glb%KappaHT
424  heattranssoln = glb%HeatTransSoln
425 
426 
427  numndsbcht = glb%NumNdsBCHT
428  bcflaght => glb%BCFlagHT
429  temperature => glb%Temperature
430  bcvalueht => glb%BCvalueHT
431 
432 
433  elemstart = 1
434 
435 ! Solve for the Heat Transfer Solution first
436 
437  DO j = 1, nummatvol
438 
439  elemend = numelpartbndrymat(j) + elemstart - 1
440 
441  ianalysistype = isolntype(j)
442 
443  DO i = 1,glb%NumNdsBCHT
444  k4 = glb%BCFlagHT(1,i) ! node
445 
446  IF (glb%BCFlagHT(2,i).EQ.0) THEN ! impose temperature
447  glb%Temperature(k4) = glb%BCvalueHT(1,i) ! *glb%prop
448 
449  ENDIF
450  ENDDO
451 
452  IF(ieltype.EQ.4)THEN
453 
454  CALL v3d4_thermal(numelvol, numnp, elconnvol, meshcoor, kappaht, &
455  rnetht, temperature, rho, cp, matidvol, nummatvol,velobar,elemstart, elemend)
456 
457  ELSE
458 
459  Call v3d10_thermal(numelvol, numnp, elconnvol, meshcoor, kappaht, &
460  rnetht, temperature, rho, cp, matidvol, nummatvol, velobar,elemstart, elemend)
461 
462  ENDIF
463 
464  elemstart = numelvolmat(j) + elemstart
465  ENDDO
466 !
467 !----- FORM THE BUFFER CONTAINING COMMUNICATED NODAL VALUES
468 !
469  ALLOCATE(buf(1:totnumndcomm/3))
470  k1 = 1
471  DO j1 = 1, totnumneighprocs
472  pndcomm => ndcommlist(j1)
473  DO j = 1, numndcomm(j1)
474  buf(k1) = rnetht(pndcomm%NdId(j))
475  k1 = k1 + 1
476  ENDDO
477  ENDDO
478 
479 !
480 !-MPI- RECEIVE THE INTERNAL FORCE VECTOR FROM THE NEIGHBORS
481 !
482  DO j1 = 1, totnumneighprocs
483  k = neighproclist(j1)+1
484  CALL mpi_irecv(recvdatafrm(k)%rcvbuf(1),numndcomm(j1), &
485  mpi_double_precision,k-1,10,mpi_comm_rocfrac, &
486  reqrcv(j1),ierr)
487  ENDDO
488 !
489 !-MPI- SEND THE INTERNAL FORCE VECTOR TO THE NEIGHBORS
490 !
491  k2 = 1
492  DO j1 = 1, totnumneighprocs
493  k = neighproclist(j1)
494  CALL mpi_isend(buf(k2), numndcomm(j1),mpi_double_precision, &
495  k,10,mpi_comm_rocfrac,reqsnd(j1),ierr)
496  k2 = k2 + numndcomm(j1)
497  ENDDO
498 
499 
500 !------ CALCULATE THE SUBMESH'S BOUNDARY INTERNAL FORCE VECTOR
501 
502  elemend = 0
503  DO j = 1, nummatvol
504 
505  elemstart = elemend + numelpartbndrymat(j) + 1
506 
507  elemend = numelvolmat(j) + elemend
508 
509  IF(ieltype.EQ.4)THEN
510 
511  CALL v3d4_thermal(numelvol, numnp, elconnvol, meshcoor, kappaht, &
512  rnetht, temperature, rho, cp, matidvol, nummatvol,velobar,elemstart, elemend)
513  ELSE
514 
515  Call v3d10_thermal(numelvol, numnp, elconnvol, meshcoor, kappaht, &
516  rnetht, temperature, rho, cp, matidvol, nummatvol, velobar,elemstart, elemend)
517 
518  ENDIF
519  ENDDO
520  IF(totnumneighprocs.GT.0)THEN
521  CALL mpi_waitall(totnumneighprocs,reqrcv,statrcv,ierr)
522  CALL mpi_waitall(totnumneighprocs,reqsnd,statsnd,ierr)
523  ENDIF
524 
525  DEALLOCATE(buf)
526 
527 !
528 !----- ADD NEIGHBOR'S CONTRIBUTION TO THE INTERNAL FORCE VECTOR
529 !
530  DO j1 = 1, totnumneighprocs
531  k = neighproclist(j1)+1
532  k1 = 1
533  pndcomm => ndcommlist(j1)
534  precvdf => recvdatafrm(k)
535  DO j = 1, numndcomm(j1)
536  k2 = pndcomm%NdId(j)
537  rnetht(k2) = rnetht(k2) + precvdf%rcvbuf(k1)
538  k1 = k1 + 1
539  ENDDO
540  ENDDO
541 
542  Do i = 1, glb%NumNP
543 
544  glb%Temperature(i) = glb%Temperature(i) + glb%DT*glb%CapctInv(i)*rnetht(i)
545  ENDDO
546 
547  DO i = 1,glb%NumNdsBCHT
548  k4 = glb%BCFlagHT(1,i) ! node
549 
550  IF (glb%BCFlagHT(2,i).EQ.0) THEN ! impose temperature
551  glb%Temperature(k4) = glb%BCvalueHT(1,i) !*glb%prop
552  ENDIF
553  ENDDO
554 
555 
556 ! Solve the Structural solution with temperature expansion
557 
558 
559  elemstart = 1
560 
561  DO j = 1, nummatvol
562 
563  elemend = numelpartbndrymat(j) + elemstart - 1
564 
565  ianalysistype = isolntype(j)
566 
567  IF(ieltype.EQ.4)THEN
568 
569  glb%S11(:,:) = 0.d0
570  glb%S22(:,:) = 0.d0
571  glb%S33(:,:) = 0.d0
572 
573  CALL internalforce_v3d4ht( glb, rnet, elemstart, elemend, ianalysistype, temperature)
574 
575 !!$ CALL v3d4_thermalExp(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,Rnet,glb%ci, &
576 !!$ glb%S11,glb%S22,glb%S33, &
577 !!$ glb%NumNP,ElemStart,ElemEnd,glb%NumElVol,glb%NumMatVol, glb%alpha, Temperature, glb%Temperature0)
578 
579  ELSE
580 
581  glb%S11(:,:) = 0.d0
582  glb%S22(:,:) = 0.d0
583  glb%S33(:,:) = 0.d0
584 
585 
586  CALL internalforce_v3d10( glb, rnet, elemstart, elemend, ianalysistype)
587 
588  CALL v3d10_thermalexp(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%ci, &
589  glb%S11,glb%S22,glb%S33, &
590  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, glb%alpha, temperature, glb%Temperature0)
591 
592  ENDIF
593 
594  elemstart = numelvolmat(j) + elemstart
595  ENDDO
596 
597 
598 !
599 !----- FORM THE BUFFER CONTAINING COMMUNICATED NODAL VALUES
600 !
601  ALLOCATE(buf(1:totnumndcomm))
602  k1 = 1
603  DO j1 = 1, totnumneighprocs
604  k = neighproclist(j1)
605  pndcomm => ndcommlist(j1)
606  DO j = 1, numndcomm(j1)
607  k2 = 3*pndcomm%NdId(j)
608  buf(k1) = rnet( k2 - 2 )
609  buf(k1+1) = rnet( k2 - 1 )
610  buf(k1+2) = rnet( k2 )
611  k1 = k1 + 3
612  ENDDO
613  ENDDO
614 
615 
616 !
617 !-MPI- RECEIVE THE INTERNAL FORCE VECTOR FROM THE NEIGHBORS
618 !
619  DO j1 = 1, totnumneighprocs
620  k = neighproclist(j1)+1
621  CALL mpi_irecv(recvdatafrm(k)%rcvbuf(1),numndcomm(j1)*3, &
622  mpi_double_precision,k-1,10,mpi_comm_rocfrac, &
623  reqrcv(j1),ierr)
624  ENDDO
625 
626 !
627 !-MPI- SEND THE INTERNAL FORCE VECTOR TO THE NEIGHBORS
628 !
629  k2 = 1
630  DO j1 = 1, totnumneighprocs
631  k = neighproclist(j1)
632  CALL mpi_isend(buf(k2), numndcomm(j1)*3,mpi_double_precision, &
633  k,10,mpi_comm_rocfrac,reqsnd(j1),ierr)
634  k2 = k2 + numndcomm(j1)*3
635  ENDDO
636 
637 !
638 !-MPI- WAIT FOR INTERNAL FORCE VECTOR COMMUNICATION TO COMPLETE
639 !
640 
641  IF(aleenabled)THEN
642  IF(ieltype.EQ.4)THEN
643  CALL v3d4_ale(velobar,accelbar,disp,velohalf,rnet, &
644  e,xnu,rho,numnp,nummatvol, &
645  numelvol,matidvol,elconnvol,meshcoor, &
646  numelpartbndry+1,numelvol)
647  ELSE
648  CALL v3d10_ale(velobar,accelbar,disp,velohalf,rnet, &
649  e,xnu,rho,numnp,nummatvol, &
650  numelvol,matidvol,elconnvol,meshcoor, &
651  numelpartbndry+1,numelvol)
652  ENDIF
653  ENDIF
654 
655 !-- (11) calculate R_in, R_damp
656 
657 !------ CALCULATE THE SUBMESH'S BOUNDARY INTERNAL FORCE VECTOR
658 
659  elemend = 0
660  DO j = 1, nummatvol
661 
662  elemstart = elemend + numelpartbndrymat(j) + 1
663 
664  elemend = numelvolmat(j) + elemend
665 
666 
667  IF(ieltype.EQ.4)THEN
668 
669  CALL internalforce_v3d4ht( glb, rnet, elemstart, elemend, ianalysistype, temperature)
670 
671 !!$ CALL v3d4_thermalExp(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,Rnet,glb%ci, &
672 !!$ glb%S11,glb%S22,glb%S33, &
673 !!$ glb%NumNP,ElemStart,ElemEnd,glb%NumElVol,glb%NumMatVol, glb%alpha, Temperature, glb%Temperature0)
674 
675  ELSE
676  CALL internalforce_v3d10( glb, rnet, elemstart, elemend, ianalysistype)
677 
678  CALL v3d10_thermalexp(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%ci, &
679  glb%S11,glb%S22,glb%S33, &
680  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, glb%alpha, temperature, glb%Temperature0)
681  ENDIF
682  ENDDO
683 
684 
685 
686  IF(totnumneighprocs.GT.0)THEN
687  CALL mpi_waitall(totnumneighprocs,reqrcv,statrcv,ierr)
688  CALL mpi_waitall(totnumneighprocs,reqsnd,statsnd,ierr)
689  ENDIF
690 
691  DEALLOCATE(buf)
692 
693 !
694 !----- ADD NEIGHBOR'S CONTRIBUTION TO THE INTERNAL FORCE VECTOR
695 !
696  DO j1 = 1, totnumneighprocs
697  k = neighproclist(j1)+1
698  k1 = 1
699  pndcomm => ndcommlist(j1)
700  precvdf => recvdatafrm(k)
701  DO j = 1, numndcomm(j1)
702  k2 = ( pndcomm%NdId(j) )*3
703  rnet(k2-2)= rnet(k2-2) + precvdf%rcvbuf(k1)
704  rnet(k2-1)= rnet(k2-1) + precvdf%rcvbuf(k1+1)
705  rnet(k2) = rnet(k2) + precvdf%rcvbuf(k1+2)
706  k1 = k1 + 3
707  ENDDO
708  ENDDO
709 
710 
711  RETURN
712  END SUBROUTINE updatestructuralht
713 
714  SUBROUTINE internalforce_v3d4( glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
715 
716  IMPLICIT NONE
717 
718  TYPE(rocfrac_global) :: glb
719  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
720 
721  INTEGER, INTENT(IN) :: elemstart, elemend, ianalysistype
722 
723  IF (ianalysistype.EQ.0) THEN
724  CALL v3d4_nl_arruda_boyce(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,&
725  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
726  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
727  glb%xmu,glb%xkappa)
728  ELSE IF(ianalysistype.EQ.1)THEN
729  CALL v3d4_nl(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
730  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
731  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol,glb%xmu,glb%xlambda)
732  ELSE IF(ianalysistype.EQ.-1)THEN
733  CALL v3d4_neohookeanincompress(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,&
734  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
735  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
736  glb%xmu,glb%xkappa)
737  ELSE
738 !------- Linear elastic
739  CALL v3d4(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
740  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
741  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol)
742  ENDIF
743 
744 ! Damping Rdamp
745 
746  IF(glb%DampEnabled)THEN
747  CALL v3d4_damping(glb%VeloHalf,rnet,glb%NumNP, &
748  glb%NumElVol,glb%ElConnVol,glb%MeshCoor, &
749  elemstart,elemend, glb%KappaDamp)
750  END IF
751 
752 
753  END SUBROUTINE internalforce_v3d4
754 
755  SUBROUTINE internalforce_v3d4ht( glb, Rnet, ElemStart, ElemEnd, iAnalysisType, Temperature)
756 
757  IMPLICIT NONE
758 
759  TYPE(rocfrac_global) :: glb
760  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
761  REAL*8, DIMENSION(1:glb%NumNP) :: temperature
762 
763  INTEGER, INTENT(IN) :: elemstart, elemend, ianalysistype
764 
765  IF (ianalysistype.EQ.0) THEN
766  CALL v3d4_nl_arruda_boyce(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,&
767  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
768  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
769  glb%xmu,glb%xkappa)
770  ELSE IF(ianalysistype.EQ.1)THEN
771  CALL v3d4_nl(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
772  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
773  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol,glb%xmu,glb%xlambda)
774  ELSE IF(ianalysistype.EQ.-1)THEN
775  CALL v3d4_neohookeanincompress(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,&
776  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
777  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
778  glb%xmu,glb%xkappa)
779  ELSE
780 !------- Linear elastic
781  CALL v3d4_thermalexp2(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
782  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
783  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
784  glb%alpha,temperature,glb%Temperature0)
785  ENDIF
786 
787 ! Damping Rdamp
788 
789  IF(glb%DampEnabled)THEN
790  CALL v3d4_damping(glb%VeloHalf,rnet,glb%NumNP, &
791  glb%NumElVol,glb%ElConnVol,glb%MeshCoor, &
792  elemstart,elemend, glb%KappaDamp)
793  END IF
794 
795 
796  END SUBROUTINE internalforce_v3d4ht
797 
798 
799  SUBROUTINE internalforce_v3d10( glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
800 
801  IMPLICIT NONE
802 
803  TYPE(rocfrac_global) :: glb
804  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
805 
806  INTEGER, INTENT(IN) :: elemstart, elemend, ianalysistype
807 
808  IF(glb%DebondPart)THEN
809 
810  CALL v3d10_nl_huang(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp, &
811  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
812  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
813  glb%STATEV_Part1,glb%STATEV_Part2,glb%NSTATEV,glb%MATRIX,glb%NMATRIX, &
814  glb%PARTICLE,glb%NPARTICLE,glb%NPARTICLETYPE,glb%INTERFAC,glb%NINTERFAC,glb%StrainTrace)
815 
816  ELSE IF(glb%DebondPart_Matous)THEN
817 
818 
819  IF(glb%Debug_State) print*,'Starting v3d10_nl_matous', elemstart,elemend
820 
821  CALL v3d10_nl_matous(glb%MeshCoor,glb%ElConnVol,rnet,glb%Disp, &
822  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
823  glb%NumNP,elemstart,elemend,glb%NumElVol, &
824  glb%p1, glb%p2, glb%Yin, glb%SoftParam, glb%BulkMod(2), glb%BulkMod(1), &
825  glb%ShrMod(2), glb%ShrMod(1), glb%PoisRat(2), glb%PoisRat(1), &
826  glb%a_eta, glb%a_zeta,&
827  glb%cm, glb%c2, glb%cd, glb%Lo, glb%L_tensor(:,:,1), &
828  glb%L_tensor(:,:,2), glb%M_tensor(:,:,1), glb%M_tensor(:,:,2), glb%L_bar, &
829  glb%StrainOld)
830 
831  IF(glb%Debug_State) print*,'Finished v3d10_nl_matous', elemstart,elemend
832 
833 
834  ELSE
835 
836 
837  IF (ianalysistype.EQ.0) THEN
838 
839  IF ( glb%ArtificialDamping)THEN
840 
841  CALL v3d10_nl_arruda_boyce_damping(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp, &
842  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
843  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
844  glb%xmu,glb%xkappa, glb%rho, glb%cd_fastest, glb%DetF_old, glb%VeloHalf, glb%Dt)
845 
846  ELSE
847 
848  CALL v3d10_nl_arruda_boyce(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp, &
849  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
850  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
851  glb%xmu,glb%xkappa)
852  ENDIF
853 
854  ELSE IF (ianalysistype.EQ.1)THEN
855 
856  IF(glb%iElIntgratn.EQ.0)THEN
857 
858  IF ( glb%ArtificialDamping)THEN
859 
860 
861  CALL v3d10_nl_damping(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
862  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
863  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol, &
864  glb%rho, glb%cd_fastest, glb%DetF_old, glb%VeloHalf, glb%Dt)
865 
866  ELSE
867 
868  CALL v3d10_nl(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
869  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
870  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol)
871  ENDIF
872  ELSE
873 
874  CALL v3d10r_nl(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci,glb%cj, &
875  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
876  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol)
877  ENDIF
878 
879  ELSE IF (ianalysistype.EQ.2)THEN
880 
881 
882  IF(glb%iElIntgratn.EQ.0)THEN
883 !------- Linear elastic
884 
885  CALL v3d10(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
886  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
887  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol)
888 
889  ELSE
890 
891  CALL v3d10_b_bar(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%ci, &
892  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
893  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol)
894 
895  ENDIF
896  ENDIF
897  endif
898 
899  END SUBROUTINE internalforce_v3d10
900 
901  SUBROUTINE internalforce_v3d8( glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
902 
903  IMPLICIT NONE
904 
905  TYPE(rocfrac_global) :: glb
906  REAL*8, DIMENSION(1:3*glb%NumNP) :: rnet
907 
908  INTEGER, INTENT(IN) :: elemstart, elemend, ianalysistype
909 
910 !------- Linear elastic
911  CALL v3d8_me(glb%MeshCoor,glb%MatIdVol,glb%ElConnVol,rnet,glb%Disp,glb%dmat, &
912  glb%S11,glb%S22,glb%S33,glb%S12,glb%S23,glb%S13, &
913  glb%NumNP,elemstart,elemend,glb%NumElVol,glb%NumMatVol,glb%Aenh,glb%enhanced_map,glb%mixed_map)
914 
915  END SUBROUTINE internalforce_v3d8
916 
917 END MODULE updatestructuralsoln
918 
subroutine v3d10(coor, matcstet, lmcstet, R_in, d, ci, S11l, S22l, S33l, S12l, S23l, S13l, numnp, nstart, nend, numcstet, numat_vol)
Definition: v3d10.f90:53
subroutine v3d4_damping(vhalf, R_in, numnp, numcstet, lmcstet, coor, nstart, nend, KappaDamp)
subroutine v3d10_nl(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol)
Definition: v3d10_nl.f90:53
subroutine c3d6nm(nsubn, nsubf, nsubn2, nsubf2, CoorOverlay, ElConnOverlay, sd_subface_parents, sd_subface_parents2, sd_subface_mate, sd_subface_nat_coors, sd_subface_nat_coors_mate, FaceOfVolEl, FaceOfVolEl2, NumNp, NumEl, ElConn, nf, nf2, MapFaceEl2Vol, MapFaceEl2Vol2, deltan, deltat, sigmax, taumax, Sinit, Rnet, Disp, Sthresh, NumMatCoh, MatID, SignFlag)
Definition: c3d6nm.f90:54
subroutine v3d4_nl_arruda_boyce(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, mu, kapp)
subroutine v3d10_b_bar(coor, matcstet, lmcstet, R_in, d, ci, S11l, S22l, S33l, S12l, S23l, S13l, numnp, nstart, nend, numcstet, numat_vol)
Definition: v3d10_B_Bar.f90:53
subroutine v3d10_nl_arruda_boyce(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, mu, kappa)
subroutine v3d10_thermal(NumEl, NumNP, ElConnVol, Coor, Kappa, Rnet, T, Rho, Cp, matcstet, numat_vol, MeshVel, ElemStart, ElemEnd)
j indices k indices k
Definition: Indexing.h:6
subroutine v3d10_nl_huang(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, STATEV_Part1, STATEV_Part2, NSTATEV, MATRIX, NMATRIX, PARTICLE, NPARTICLE, NPARTICLETYPE, INTERFAC, NINTERFAC, StrainTrace)
subroutine internalforce_v3d4(glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
subroutine updatestructural(glb, NumProcs, Rnet)
subroutine v3d10_thermalexp(coor, matcstet, lmcstet, R_in, ci, S11l, S22l, S33l, numnp, nstart, nend, numcstet, numat_vol, CoeffExp, Temperature, Temperature0)
subroutine v3d4_nl(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, xmu, xlambda)
Definition: v3d4_nl.f90:53
subroutine internalforce_v3d8(glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
subroutine v3d10r_nl(coor, matcstet, lmcstet, R_in, d, ci, cj, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol)
Definition: v3d10r_nl.f90:53
subroutine v3d4_thermalexp2(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, CoeffExp, Temperature, Temperature0)
subroutine updatestructuralht(glb, NumProcs, Rnet, RnetHT)
subroutine v3d4_thermal(NumEl, NumNP, ElConnVol, Coor, Kappa, Rnet, T, Rho, Cp, matcstet, numat_vol, MeshVelo, ElemStart, ElemEnd)
subroutine v3d4_neohookeanincompress(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, xmu, xkappa)
blockLoc i
Definition: read.cpp:79
subroutine v3d10_nl_damping(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, rho, cd_fastest, DetFold, velo, dt)
subroutine v3d4(coor, matcstet, lmcstet, R_in, d, ci, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol)
Definition: v3d4.f90:53
subroutine v3d10_nl_matous(coor, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, p1, p2, Yin, SoftParam, Km, K2, Gm, G2, vm, nu2, a_eta, a_zeta, cm, c2, cd, Lo, Lm, L2, Mm, M2, L_bar, StrainOld)
virtual std::ostream & print(std::ostream &os) const
j indices j
Definition: Indexing.h:6
subroutine v3d8_me(coor, MatType, ElConnVol, Rnet, disp, dmat, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, NumEL, NumMatType, Aenh, enhanced_map, mixed_map)
Definition: v3d8_me.f90:53
subroutine internalforce_v3d4ht(glb, Rnet, ElemStart, ElemEnd, iAnalysisType, Temperature)
subroutine v3d10_ale(v_bar, a_bar, d, vhalf, Rnet, E, xnu, rho, numnp, numat_vol, numlstet, matlstet, lmlstet, meshcoor, nstart, nend)
Definition: v3d10_ale.f90:65
subroutine internalforce_v3d10(glb, Rnet, ElemStart, ElemEnd, iAnalysisType)
subroutine v3d10_nl_arruda_boyce_damping(coor, matcstet, lmcstet, R_in, d, S11, S22, S33, S12, S23, S13, numnp, nstart, nend, numcstet, numat_vol, mu, kappa, rho, cd_fastest, DetFold, velo, dt)
subroutine v3d4_ale(v_bar, a_bar, d, vhalf, Rnet, E, xnu, rho, numnp, numat_vol, numcstet, matcstet, lmcstet, meshcoor, nstart, nend)
Definition: v3d4_ale.f90:53