Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
utilities/RocfracPrep/read_patran.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 SUBROUTINE read_patran(numvertx2d,dhmin,nprocs)
54 
55  USE linked_list
56  USE meshdata
57  USE linked_list2
58 
59  IMPLICIT NONE
60 
61  INTEGER :: numvertx2d
62  REAL*8 :: dhmin
63 
64 ! Local
65  REAL*8 :: xx,yy,zz,size1,size2,size3,size4,size5,size6
66  REAL*8 :: dt_courant
67  REAL*8, DIMENSION(1:6) :: disflagvalue, tmpval
68  INTEGER :: numdisflag
69 
70  INTEGER :: id
71  INTEGER :: i, j
72  INTEGER :: itype
73  INTEGER :: n1,n2,n3,n4,n5,n6,n7,n8
74  INTEGER :: iface
75  REAL*8 :: value
76  REAL*8 :: press
77 !-- Tempory holding array of partitioned metis arrays
78  INTEGER, ALLOCATABLE, DIMENSION(:) :: npart
79  INTEGER :: edgecut
80  INTEGER :: nprocs
81  INTEGER :: ip
82 !
83  INTEGER :: iaux,iaux1,iaux2
84  INTEGER, ALLOCATABLE, DIMENSION(:) :: imin,nmin,imax,nmax,ninc
85  INTEGER, ALLOCATABLE, DIMENSION(:) :: imap
86  INTEGER, ALLOCATABLE, DIMENSION(:,:) :: lm4node
87  INTEGER :: nnd1, nnd2, nnd3, nnd4, nnd5, nnd6, nnd7, nnd8, nnd9, nnd10
88  INTEGER :: numnp4node
89  integer, dimension(1:6) :: disflag
90  INTEGER :: ifaceid, itmp
91 
92 
93  INTEGER :: procid
94 
95 
96  LOGICAL :: hex8, tet4, tet10, fileexist
97  LOGICAL :: fileexist1, fileexist2, fileexist3, fileexist4, fileexist5, fileexist6
98  integer :: numgeombodies,iunit,ibody
99 
100  INTEGER, POINTER, DIMENSION(:) :: numnp_glb,numel_glb,nummat_glb
101 
102  INTEGER :: ielemtest, icnt, inodetest, minel, maxel,maxnd, minnd, iel10
103 
104  INTEGER, POINTER, DIMENSION(:) :: epart_loc
105 
106  INTEGER, POINTER, dimension(:) :: procdist
107 
108  TYPE(link_ptr_type) :: link
109 
110  INTEGER :: accumel, accumnd, accumnd_old, accumel_old
111 
112  INTEGER :: ierror, iv, kc
113 
114  size1 = 0.d0
115  size2 = 0.d0
116  size3 = 0.d0
117  size4 = 0.d0
118  size5 = 0.d0
119  size6 = 0.d0
120 
121  ierror = 0
122 
123  hex8 = .false.
124  tet4 = .false.
125  tet10 = .false.
126  overlaymesh = .false.
127  interactmesh = .false.
128 
129  print*,'MESH OPTION:'
130  print*,' READING PATRAN MESH'
131  print*,' '
132 
133  itmp = 0
134  maxnumbc_str = 0
135  maxnumbc_mm = 0
136  maxnumbc_th = 0
137 
138  numndhistory = 0
139 
140  ALLOCATE(numelhex2d(1:5,1:nprocs))
141  ALLOCATE(numeltet2d(1:5,1:nprocs))
142 
143  numelhex2d(:,:) = 0
144  numeltet2d(:,:) = 0
145 
146  fileexist1 = .false.
147  fileexist2 = .false.
148  fileexist3 = .false.
149  fileexist4 = .false.
150  fileexist5 = .false.
151  fileexist6 = .false.
152 
153  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.1.out', exist=fileexist1)
154  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.2.out', exist=fileexist2)
155  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.3.out', exist=fileexist3)
156  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.4.out', exist=fileexist4)
157  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.5.out', exist=fileexist5)
158  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.6.out', exist=fileexist6)
159 
160  numgeombodies = 1
161 
162  IF(fileexist6)THEN
163  numgeombodies = 6
164  OPEN(106,file='Modin/'//prefx(1:prefx_lngth)//'.6.out')
165  OPEN(105,file='Modin/'//prefx(1:prefx_lngth)//'.5.out')
166  OPEN(104,file='Modin/'//prefx(1:prefx_lngth)//'.4.out')
167  OPEN(103,file='Modin/'//prefx(1:prefx_lngth)//'.3.out')
168  OPEN(102,file='Modin/'//prefx(1:prefx_lngth)//'.2.out')
169  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
170  ELSE IF (fileexist5)THEN
171  numgeombodies = 5
172  OPEN(105,file='Modin/'//prefx(1:prefx_lngth)//'.5.out')
173  OPEN(104,file='Modin/'//prefx(1:prefx_lngth)//'.4.out')
174  OPEN(103,file='Modin/'//prefx(1:prefx_lngth)//'.3.out')
175  OPEN(102,file='Modin/'//prefx(1:prefx_lngth)//'.2.out')
176  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
177  ELSE IF (fileexist4)THEN
178  numgeombodies = 4
179  OPEN(104,file='Modin/'//prefx(1:prefx_lngth)//'.4.out')
180  OPEN(103,file='Modin/'//prefx(1:prefx_lngth)//'.3.out')
181  OPEN(102,file='Modin/'//prefx(1:prefx_lngth)//'.2.out')
182  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
183  ELSE IF (fileexist3)THEN
184  numgeombodies = 3
185  OPEN(103,file='Modin/'//prefx(1:prefx_lngth)//'.3.out')
186  OPEN(102,file='Modin/'//prefx(1:prefx_lngth)//'.2.out')
187  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
188  ELSE IF (fileexist2) THEN
189  numgeombodies = 2
190  OPEN(102,file='Modin/'//prefx(1:prefx_lngth)//'.2.out')
191  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
192  ELSE IF (fileexist1) THEN
193  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.1.out')
194  ELSE
195  fileexist = .false.
196 
197  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.pat', exist=fileexist)
198 
199  IF (.NOT. fileexist)THEN
200  print*,'File '//'Modin/'//prefx(1:prefx_lngth)//'.pat NOT found'
201  print*,'...Trying '//'Modin/'//prefx(1:prefx_lngth)//'.out'
202 
203  fileexist = .false.
204  INQUIRE (file='Modin/'//prefx(1:prefx_lngth)//'.out', exist=fileexist)
205 
206  IF (.NOT. fileexist)THEN
207  print*,'ERROR: File '//'Modin/'//prefx(1:prefx_lngth)//'.out NOT found'
208  print*,'ERROR: No Patran Neutral file Found, stopping'
209  stop
210  ELSE
211  print*,'File '//'Modin/'//prefx(1:prefx_lngth)//'.out found'
212 
213  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.out', form='formatted')
214  ENDIF
215  ELSE
216  OPEN(101,file='Modin/'//prefx(1:prefx_lngth)//'.pat', form='formatted')
217  ENDIF
218 
219  ENDIF
220 
221  print*,'No. of Mesh Segment Files Found =', numgeombodies
222 
223  ALLOCATE(numnp_glb(1:numgeombodies),numel_glb(1:numgeombodies),nummat_glb(1:numgeombodies))
224 
225  DO ibody = 1, numgeombodies
226  iunit = 100 + ibody
227 
228 
229 !
230 ! - Packet Type 25: Title Card, Format(i2,8i8)
231  READ(iunit,'()')
232  READ(iunit,'()')
233 
234 ! - Packet Type 26: Summary Data, Format(i2,8i8)
235 ! - 26 ID IV KC N1 N2 N3 N4 N5
236 ! - N1 = number of nodes
237 ! - N2 = number of elements
238 ! - N3 = number of materials
239 ! - N4 = number of Element Properties
240 ! - N5 = number of Coordinate Frames
241 
242  READ(iunit,*) i,i,i,i,numnp_glb(ibody),numel_glb(ibody),nummat_glb(ibody)
243 
244  IF(nummat_glb(ibody).LE.0) nummat_glb(ibody) = 1
245 
246 ! - part of title card
247  READ(iunit,'()')
248 
249  ENDDO
250 
251  numnp_prmry = sum(numnp_glb)
252  numelv_prmry = sum(numel_glb)
253  nummat = maxval(nummat_glb)
254 
255  print*,' No. of elements = ', numelv_prmry
256  print*,' No. of nodes = ', numnp_prmry
257  print*,' No. of Materials = ', nummat
258  print*,' No. of vertex=',numvertx
259 
260  inodetest = 0
261  ielemtest = 0
262 
263  iaux = 0
264 
265  ALLOCATE(epart(1:numelv_prmry))
266 
267  accumnd = 0
268 
269  accumel = 0
270 
271  DO ibody = 1, numgeombodies
272  iunit = 100 + ibody
273  numnp4node = 0
274 !
275 ! -- Read Nodal coordinates
276 
277  IF(ibody.EQ.1)THEN
278  ALLOCATE(coor(1:3,1:numnp_prmry),lmelv_prmry(1:numvertx,1:numelv_prmry))
279 
280 !!$ IF(numvertx.NE.4)THEN
281 !!$ ALLOCATE(lm4node( 1:4,1:numelv_prmry))
282 !!$ ALLOCATE(imap(1:numnp_prmry))
283 !!$ imap(:) = 0
284 !!$ numnp4node = 0
285 !!$ ELSE
286 !!$ numnp4node = numnp_prmry
287 !!$ ENDIF
288  ENDIF
289 
290  iel10 = 0
291 
292 ! ConvertUnit = .0254d0 ! for titan, units in engles
293 
294  DO i = 1, numnp_glb(ibody)
295 
296 ! - Type 01: Node Data, format(i2,8i8)
297 ! 1 ID IV KC
298 ! ID = node id
299 ! IV = 0 n/a
300 ! KC = 2
301  READ(iunit,*) j,id
302  id = id + accumnd
303 ! - format(3e16.9)
304 ! - caresian coordinate of Nodes x, y, z
305  READ(iunit,'(3e16.9)') coor(1:3,id)
306  coor(1:3,id) = coor(1:3,id)*convertunit
307 ! - ICF GTYPE NDF CONFIG CID PSPC
308  READ(iunit,'()')
309 
310  inodetest = inodetest + 1
311  ENDDO
312  accumnd_old = accumnd
313  accumnd = accumnd + numnp_glb(ibody)
314 !
315 ! -- Read element connectivity array
316  IF(ibody.EQ.1)THEN
317  ALLOCATE(matid(1:numelv_prmry))
318  ALLOCATE(eltypeid(1:numelv_prmry))
319  ENDIF
320 ! flages for element type id
321 !
322 ! 4 = 4 node tetrahedral
323 ! 8 = 8 node hexahedral
324 ! 10 = 10 node tetrahedral
325 ! 12 = 12 node wedge*
326 ! 15 = 15 node wedge*
327 ! 20 = 20 node hexahdral*
328 !
329 ! * Not yet implemented
330 
331  minel = 1e9
332  maxel = 0
333 
334  element: DO i = 1, numel_glb(ibody)
335 
336 ! - Type 02: Element Data, format(i2,8i8)
337 ! 2 ID IV KC N1
338 ! ID = element ID
339 ! IV = Shape (5 = tet)
340  READ(iunit,*) j, id
341  ielemtest = ielemtest + 1
342  accumel_old = accumel
343  id = accumel + id
344 
345 
346 ! NODES CONFIG CID CEID
347  READ(iunit,'(3i8)') numvertx,j, matid(id)
348  IF(numvertx.NE.4)THEN
349  IF(numvertx.NE.10)THEN
350  IF(numvertx.NE.8)THEN
351  print*,'ERROR: FOUND UNSUPPORTED ELEMENT TYPE'
352  print*,'Found element with ', numvertx,' nodes '
353  print*,'Stopping'
354  stop
355  ENDIF
356  ENDIF
357  ENDIF
358 
359  eltypeid(id) = numvertx
360 
361  IF(matid(id).LE.0) matid(id) = 1
362 ! LNODES
363 ! LNODES = Element corner nodes followed by additional nodes
364  READ(iunit,*) lmelv_prmry(1:numvertx,id)
365  lmelv_prmry(1:numvertx,id) = lmelv_prmry(1:numvertx,id) + accumnd_old
366 
367  iel10 = iel10 + 1
368  IF(numvertx.EQ.10.AND.i.EQ.1.AND.nprocs.GT.1)THEN
369  ALLOCATE(lm4node( 1:4,1:numel_glb(ibody)))
370  IF(ibody.EQ.1) ALLOCATE(imap(1:numnp_prmry))
371  imap(:) = 0
372  print*,'Re-setting imap'
373  ENDIF
374  IF(numvertx.EQ.4.AND.i.EQ.1.AND.nprocs.GT.1)THEN
375  ALLOCATE(lm4node( 1:4,1:numel_glb(ibody)))
376  IF(ibody.EQ.1) ALLOCATE(imap(1:numnp_prmry))
377  imap(:) = 0
378  print*,'Re-setting imap'
379  ENDIF
380  IF(numvertx.EQ.10.AND.nprocs.GT.1)THEN
381  DO j = 1, 4
382  IF(imap(lmelv_prmry(j,id)).EQ.0)THEN
383  numnp4node = numnp4node + 1
384  imap(lmelv_prmry(j,id)) = numnp4node
385  ENDIF
386  iaux = iaux + 1
387  lm4node(j,iel10) = imap(lmelv_prmry(j,id))
388  ENDDO
389 
390  ELSE IF(numvertx.EQ.4.AND.nprocs.GT.1)THEN
391  DO j = 1, 4
392  IF(imap(lmelv_prmry(j,id)).EQ.0)THEN
393  numnp4node = numnp4node + 1
394  imap(lmelv_prmry(j,id)) = numnp4node
395  ENDIF
396  iaux = iaux + 1
397  lm4node(j,iel10) = imap(lmelv_prmry(j,id))
398  ENDDO
399  ENDIF
400  maxel = sum(numel_glb(1:ibody)) ! SUM( MAX(MaxEl,id)
401  minel = accumel_old + 1 !MIN(,id)
402 
403 
404 !
405 ! -- Find the size of the smallest element
406 !
407  xx = coor(1,lmelv_prmry(1,id)) - coor(1,lmelv_prmry(2,id))
408  yy = coor(2,lmelv_prmry(1,id)) - coor(2,lmelv_prmry(2,id))
409  zz = coor(3,lmelv_prmry(1,id)) - coor(3,lmelv_prmry(2,id))
410  size1 = sqrt(xx*xx+yy*yy+zz*zz)
411  xx = coor(1,lmelv_prmry(2,id)) - coor(1,lmelv_prmry(3,id))
412  yy = coor(2,lmelv_prmry(2,id)) - coor(2,lmelv_prmry(3,id))
413  zz = coor(3,lmelv_prmry(2,id)) - coor(3,lmelv_prmry(3,id))
414  size2 = sqrt(xx*xx+yy*yy+zz*zz)
415  xx = coor(1,lmelv_prmry(3,id)) - coor(1,lmelv_prmry(1,id))
416  yy = coor(2,lmelv_prmry(3,id)) - coor(2,lmelv_prmry(1,id))
417  zz = coor(3,lmelv_prmry(3,id)) - coor(3,lmelv_prmry(1,id))
418  size3 = sqrt(xx*xx+yy*yy+zz*zz)
419  xx = coor(1,lmelv_prmry(4,id)) - coor(1,lmelv_prmry(1,id))
420  yy = coor(2,lmelv_prmry(4,id)) - coor(2,lmelv_prmry(1,id))
421  zz = coor(3,lmelv_prmry(4,id)) - coor(3,lmelv_prmry(1,id))
422  size4 = sqrt(xx*xx+yy*yy+zz*zz)
423  xx = coor(1,lmelv_prmry(4,id)) - coor(1,lmelv_prmry(2,id))
424  yy = coor(2,lmelv_prmry(4,id)) - coor(2,lmelv_prmry(2,id))
425  zz = coor(3,lmelv_prmry(4,id)) - coor(3,lmelv_prmry(2,id))
426  size5 = sqrt(xx*xx+yy*yy+zz*zz)
427  xx = coor(1,lmelv_prmry(4,id)) - coor(1,lmelv_prmry(3,id))
428  yy = coor(2,lmelv_prmry(4,id)) - coor(2,lmelv_prmry(3,id))
429  zz = coor(3,lmelv_prmry(4,id)) - coor(3,lmelv_prmry(3,id))
430  size6 = sqrt(xx*xx+yy*yy+zz*zz)
431  dhmin = min(size1,size2,size3,size4,size5,size6,dhmin)
432  ENDDO element
433 
434  print*,'Done reading Element'
435  accumel = accumel + numel_glb(ibody)
436 
437  IF(nprocs.GT.1)THEN
438  IF(numvertx.EQ.10)THEN
439  ALLOCATE(npart(1:numnp4node),stat=ierror)
440  IF(ierror .NE.0)THEN
441  ! Space for npart could not be allcoated
442  print*,'Program could not allocate space for npart'
443  print*,'Dimensions 1 to ', numnp4node
444  stop
445  ENDIF
446 
447 !!$ IF(ibody.EQ.4) THEN
448 !!$ WRITE(44,*) NumEL_glb(ibody),numnp4node,nprocs
449 !!$ MaxNd = MAXVAL(lm4node)
450 !!$ MinNd = MINVAL(lm4node)
451 !!$ PRINT*,'MaxNd =', MaxNd
452 !!$ PRINT*,'MinND =', MinNd
453 !!$ PRINT*,'MinNDlocation',MINLOC(lm4node)
454 !!$ PRINT*,'Maximum renumbered node =', numnp4node
455 !!$ PRINT*,'Number of elements in section',NumEL_glb(ibody)
456 !!$ PRINT*,'MinEl:MaxEl',MinEl,MaxEl
457 !!$ DO i = 1, NumEL_glb(ibody)
458 !!$ WRITE(44,*) lm4node(:,i)
459 !!$ IF(ANY(lm4node(:,i) .EQ. 0)) THEN
460 !!$ PRINT*,'zero connectivity'
461 !!$ STOP
462 !!$ ENDIF
463 !!$ ENDDO
464 !!$ CLOSE(44)
465 !!$ ENDIF
466 ! PRINT*,'METIS for elements ',MinEL,':',MaxEl
467 
468 
469 !!$ CALL METIS_PartMeshDual(NumEL_glb(ibody),numnp4node, &
470 !!$ lm4node,2,1,nprocs,edgecut,epart(MinEl:MaxEl),npart)
471 
472  print*,'METIS for elements ',minel,':',maxel,numel_glb(ibody)
473 
474  ALLOCATE(epart_loc(1:numel_glb(ibody)),stat=ierror)
475 
476  IF(ierror .NE.0)THEN
477  ! Space for npart could not be allcoated
478  print*,'Program could not allocate space for epart_loc'
479  print*,'Dimensions 1 to ', numel_glb(ibody)
480  stop
481  ENDIF
482 
483  print*,'CALLING METIS'
484 
485  CALL metis_partmeshnodal(numel_glb(ibody),numnp4node, &
486  lm4node,2,1,nprocs,edgecut,epart_loc,npart)
487 
488  epart(minel:maxel) = epart_loc(1:numel_glb(ibody))
489  print*,minel,maxel,1,numel_glb(ibody)
490  deallocate(epart_loc)
491 
492  print*,'Finished Metis'
493  DEALLOCATE(npart)
494  DEALLOCATE(lm4node)
495 
496  ELSE IF(numvertx.EQ.4)THEN
497  ALLOCATE(npart(1:numnp_glb(ibody)),stat=ierror)
498  IF(ierror .NE.0)THEN
499  ! Space for npart could not be allcoated
500  print*,'Program could not allocate space for npart'
501  print*,'Dimensions 1 to ', numnp4node
502  stop
503  ENDIF
504 
505 !!$ CALL METIS_PartMeshDual(NumEL_glb(ibody),numnp4node, &
506 !!$ lm4node,2,1,nprocs,edgecut,epart(MinEl:MaxEl),npart)
507 
508  print*,'METIS for elements ',minel,':',maxel,numel_glb(ibody)
509 
510  ALLOCATE(epart_loc(1:numel_glb(ibody)),stat=ierror)
511 
512  IF(ierror .NE.0)THEN
513  ! Space for npart could not be allcoated
514  print*,'Program could not allocate space for epart_loc'
515  print*,'Dimensions 1 to ', numel_glb(ibody)
516  stop
517  ENDIF
518 
519  print*,'CALLING METIS',numel_glb(ibody),numnp_glb(ibody)
520 
521  CALL metis_partmeshnodal(numel_glb(ibody),numnp_glb(ibody), &
522  lm4node,2,1,nprocs,edgecut,epart_loc,npart)
523 
524  epart(minel:maxel) = epart_loc(1:numel_glb(ibody))
525  print*,minel,maxel,1,numel_glb(ibody)
526  deallocate(epart_loc)
527 
528  print*,'Finished Metis'
529  DEALLOCATE(npart)
530  DEALLOCATE(lm4node)
531 
532 
533  ENDIF
534  ELSE
535  epart = 1
536  ENDIF
537  ENDDO
538 
539 !!$
540 !!$ OPEN(45,file='LoadBalanceStats.out')
541 !!$ ALLOCATE(ProcDist(1:nprocs))
542 !!$ ProcDist(:) = 0
543 !!$ DO i = 1, numelv_prmry
544 !!$ IF(epart(i).EQ.0)THEN
545 !!$ print*,'epart = 0',i
546 !!$ stop
547 !!$ endif
548 !!$ ProcDist(epart(i)) = ProcDist(epart(i)) + 1
549 !!$ ENDDO
550 !!$
551 !!$ DO i=1, nprocs
552 !!$ write(45,*) i, ProcDist(i)
553 !!$ enddo
554 !!$ PRINT*,'*** Load Balancing Stats ***'
555 !!$ PRINT*,'Maximum number of elements on a processor =', MAXVAL(ProcDist(:))
556 !!$ PRINT*,'Minimum number of elements on a processor =', MINVAL(ProcDist(:))
557 !!$ close(45)
558 !!$ DEALLOCATE(ProcDist)
559 
560 
561 
562  IF(inodetest.NE.numnp_prmry)THEN
563  print*,'ERROR number of combined nodes not equal total nodes'
564  print*,'Sum of Nodes =', numnp_prmry
565  print*,'Actual Number Read =', inodetest
566  stop
567  ENDIF
568 
569  IF(ielemtest.NE.numelv_prmry)THEN
570  print*,'ERROR number of combined elements not equal total elements'
571  print*,'Sum of Elements =', numelv_prmry
572  print*,'Actual Number Read =', ielemtest
573  stop
574  ENDIF
575 
576 ! -- Partition the finite element mesh
577 
578  print*,' REQUESTED NUMBER OF PARTITIONS =',nprocs
579 
580 !
581 ! Call METIS using the partition the mesh
582 !
583 
584 
585  print*,'CALLING METIS'
586 
587  IF(nprocs.GT.1)THEN
588 !-ALT CALL METIS_PartMeshNodal(numel_old_z,nn,
589 !-ALT$ elmnts,1,1,nprocs,edgecut,epart_p,npart_p)
590  IF(numvertx.EQ.8)THEN
591  ALLOCATE(npart(1:numnp_prmry))
592  CALL metis_partmeshdual(numelv_prmry,numnp_prmry, &
593  lmelv_prmry,3,1,nprocs,edgecut,epart,npart)
594  DEALLOCATE(npart)
595  ENDIF
596 !!$ ELSE IF(numvertx.EQ.4)THEN
597 !!$ ALLOCATE(npart(1:numnp_prmry))
598 !!$ CALL METIS_PartMeshDual(numelv_prmry,numnp_prmry, &
599 !!$ lmelv_prmry,2,1,nprocs,edgecut,epart,npart)
600 !!$ DEALLOCATE(npart)
601 !!$ ENDIF
602  ELSE
603  epart(:) = 1
604  ENDIF
605 
606  print*,' Called METIS'
607  OPEN(45,file='LoadBalanceStats.out')
608  ALLOCATE(procdist(1:nprocs))
609  procdist(:) = 0
610  DO i = 1, numelv_prmry
611  IF(epart(i).EQ.0)THEN
612  print*,'epart = 0',i
613  stop
614  endif
615  procdist(epart(i)) = procdist(epart(i)) + 1
616  ENDDO
617 
618  DO i=1, nprocs
619  write(45,*) i, procdist(i)
620  enddo
621  print*,'*** Load Balancing Stats ***'
622  print*,'Maximum number of elements on a processor =', maxval(procdist(:))
623  print*,'Minimum number of elements on a processor =', minval(procdist(:))
624  close(45)
625  DEALLOCATE(procdist)
626 
627 
628 ! create communication file ! Note: should be able to remove restriction
629 
630  ALLOCATE(procndlist(1:numnp_prmry,1:maxnumberofprocstosharenode) )
631  ALLOCATE(numprocpernd(1:numnp_prmry))
632  ALLOCATE(numelperproc(1:nprocs))
633  ALLOCATE(numndperproc(1:nprocs))
634 
635  numndperproc(:) = 0
636  numelperproc(:) = 0
637 
638  print*,'Calling NewCommList'
639  CALL newcommlist(numelv_prmry, numnp_prmry, nprocs, numvertx, &
640  lmelv_prmry, epart,numprocpernd,procndlist,maxnumberofprocstosharenode,numelperproc, &
641  numndperproc)
642 
643  print*,' .. completed'
644 
645 ! -- create a view of the partitioned mesh
646 ! -- PMVIS software
647 ! -- Command: pmvis.sgi.bin -n pmvis.nod -c pmvis.ele -p pmvis.part -o 1
648 
649  iopmvis = 0
650 
651  IF(iopmvis.EQ.1)THEN
652 
653  OPEN(13,file='pmvis.nod')
654  DO i = 1, numnp_prmry
655  WRITE(13,'(3e16.9)') coor(1:3,i)
656  ENDDO
657  CLOSE(13)
658  OPEN(13,file='pmvis.ele')
659  DO i = 1, numelv_prmry
660  WRITE(13,'(4i10)') lmelv_prmry(1:4,i)
661  ENDDO
662  CLOSE(13)
663 
664  OPEN(13,file='pmvis.part')
665  DO i = 1, numelv_prmry
666  WRITE(13,'(1i10)') epart(i)
667  ENDDO
668  CLOSE(13)
669  ENDIF
670 !
671 !
672 ! -- Continue to read in the rest of the input parameters
673 
674  numbc_prmry = 0
675  numbc_prmry_mm = 0
676  numbc_prmry_ht = 0
677  numserbc = 0
678 
679 !!$ ALLOCATE(numel_2d(1:nprocs,1:2))
680 !!$ numel_2d(:,:) = 0
681 
682 
683  ALLOCATE(indsburnflg(1:numnp_prmry))
684 
685  indsburnflg(:) = 0
686 
687 ! Initialize list for boundary conditions
688 
689  nullify(bc_structural_head,bc_structural_tail)
690  nullify(bc_meshmotion_head,bc_meshmotion_tail)
691  nullify(bc_thermal_head,bc_thermal_tail)
692 
693  nullify(surfmesh_tri3_ov1_head,surfmesh_tri3_ov1_tail)
694  nullify(surfmesh_tri3_ov2_head,surfmesh_tri3_ov2_tail)
695  nullify(surfmesh_tri3_s_head,surfmesh_tri3_s_tail)
696  nullify(surfmesh_tri3_sf_head,surfmesh_tri3_sf_tail)
697  nullify(surfmesh_tri6_s_head,surfmesh_tri6_s_tail)
698  nullify(surfmesh_tri6_sf_head,surfmesh_tri6_sf_tail)
699  nullify(surfmesh_hex8_s_head,surfmesh_hex8_s_tail)
700  nullify(surfmesh_hex8_sf_head,surfmesh_hex8_sf_tail)
701 
702 ! number of boundary conditions per processors
703 
704  ALLOCATE(numbc_structural(1:nprocs))
705  ALLOCATE(numbc_meshmotion(1:nprocs))
706  ALLOCATE(numbc_thermal(1:nprocs))
707  ALLOCATE(numbc_flag(1:nprocs))
708  numbc_structural(:) = 0
709  numbc_meshmotion(:) = 0
710  numbc_thermal(:) = 0
711  numbc_flag(:) = 0
712  ALLOCATE(bc_flag(1:3,1:numnp_prmry))
713 
714  bc_flag(:,:) = 0
715 
716 
717  print*,'FINISH READING PATRAN FILE'
718  print*,'Reading Boundary Conditions'
719  accumel = 0
720  accumnd = 0
721  DO ibody = 1, numgeombodies
722  iunit = 100 + ibody
723 
724 
725  DO
726  READ(iunit,*) itype,id,iv,kc
727  IF(itype.EQ.99) EXIT
728 
729  IF(itype.EQ.4)THEN
730  READ(iunit,'()')
731 
732 ! Marks of IntFaceFlag :
733 !
734 ! SolidFluid Interface = 1
735 ! NotASolidFluid Interface = 0
736 
737  ELSE IF(itype.EQ. 3) THEN
738  DO i = 1, 20
739  READ(iunit,'()')
740  ENDDO
741  ELSE IF(itype .EQ. 6)THEN ! pressure loading
742  id = id + accumel
743  ip = epart(id)
744  READ(iunit,'(i1,i1,i1,i6,8i1)')i,i,i,i,n1,n2,n3,n4,n5,n6,n7,n8
745  READ(iunit,*) press
746  intfaceflag = abs(int(press))
747 
748  IF(.NOT.(interactmesh))THEN
749  IF(intfaceflag.GE.0.AND.intfaceflag.LE.2) interactmesh = .true.
750  ENDIF
751 
752 ! tet elements
753 
754  IF(n1.EQ.1.AND.n2.EQ.1.AND.n3.EQ.1 &
755  .AND.n4.EQ.0.AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.0)THEN
756  IF(eltypeid(id).EQ.4)THEN
757  nnd1 = lmelv_prmry(1,id)
758  nnd2 = lmelv_prmry(3,id)
759  nnd3 = lmelv_prmry(2,id)
760  !itmp = itmp + 1
761  ifaceid = 1
762  ELSE
763  nnd1 = lmelv_prmry(1,id)
764  nnd2 = lmelv_prmry(3,id)
765  nnd3 = lmelv_prmry(2,id)
766  nnd4 = lmelv_prmry(7,id)
767  nnd5 = lmelv_prmry(6,id)
768  nnd6 = lmelv_prmry(5,id)
769  ifaceid = 1
770  ENDIF
771  ELSE IF(n1.EQ.1.AND.n2.EQ.1.AND.n4.EQ.1 &
772  .AND.n3.EQ.0.AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.0)THEN
773  IF(eltypeid(id).EQ.4)THEN
774  nnd1 = lmelv_prmry(1,id)
775  nnd2 = lmelv_prmry(2,id)
776  nnd3 = lmelv_prmry(4,id)
777  !itmp = itmp + 1
778  ifaceid = 2
779  ELSE
780  nnd1 = lmelv_prmry(1,id)
781  nnd2 = lmelv_prmry(2,id)
782  nnd3 = lmelv_prmry(4,id)
783  nnd4 = lmelv_prmry(5,id)
784  nnd5 = lmelv_prmry(9,id)
785  nnd6 = lmelv_prmry(8,id)
786  ifaceid = 2
787  ENDIF
788  ELSE IF(n2.EQ.1.AND.n3.EQ.1.AND.n4.EQ.1 &
789  .AND.n1.EQ.0.AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.0)THEN
790  IF(eltypeid(id).EQ.4)THEN
791  nnd1 = lmelv_prmry(2,id)
792  nnd2 = lmelv_prmry(3,id)
793  nnd3 = lmelv_prmry(4,id)
794  !itmp = itmp + 1
795  ifaceid = 3
796  ELSE
797  nnd1 = lmelv_prmry(2,id)
798  nnd2 = lmelv_prmry(3,id)
799  nnd3 = lmelv_prmry(4,id)
800  nnd4 = lmelv_prmry(6,id)
801  nnd5 = lmelv_prmry(10,id)
802  nnd6 = lmelv_prmry(9,id)
803  ifaceid = 3
804  ENDIF
805  ELSE IF(n1.EQ.1.AND.n3.EQ.1.AND.n4.EQ.1 &
806  .AND.n2.EQ.0.AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.0)THEN
807  IF(eltypeid(id).EQ.4)THEN
808  nnd1 = lmelv_prmry(4,id)
809  nnd2 = lmelv_prmry(3,id)
810  nnd3 = lmelv_prmry(1,id)
811  itmp = itmp + 1
812  ifaceid = 4
813  ELSE
814  nnd1 = lmelv_prmry(4,id)
815  nnd2 = lmelv_prmry(3,id)
816  nnd3 = lmelv_prmry(1,id)
817  nnd4 = lmelv_prmry(10,id)
818  nnd5 = lmelv_prmry(7,id)
819  nnd6 = lmelv_prmry(8,id)
820  ifaceid = 4
821  ENDIF
822 ! Hex elements
823  ELSE IF(n1.EQ.1.AND.n2.EQ.1.AND.n3.EQ.1.AND.n4.EQ.1 &
824  .AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.0)THEN
825  IF(eltypeid(id).EQ.8)THEN
826  nnd1 = lmelv_prmry(4,id)
827  nnd2 = lmelv_prmry(3,id)
828  nnd3 = lmelv_prmry(2,id)
829  nnd4 = lmelv_prmry(1,id)
830  itmp = itmp + 1
831  ifaceid = 1
832  ENDIF
833  ELSE IF(n1.EQ.0.AND.n2.EQ.0.AND.n3.EQ.0.AND.n4.EQ.0 &
834  .AND.n5.EQ.1.AND.n6.EQ.1.AND.n7.EQ.1.AND.n8.EQ.1)THEN
835  IF(eltypeid(id).EQ.8)THEN
836  nnd1 = lmelv_prmry(5,id)
837  nnd2 = lmelv_prmry(6,id)
838  nnd3 = lmelv_prmry(7,id)
839  nnd4 = lmelv_prmry(8,id)
840  itmp = itmp + 1
841  ifaceid = 2
842  ENDIF
843  ELSE IF(n1.EQ.1.AND.n2.EQ.1.AND.n3.EQ.0.AND.n4.EQ.0 &
844  .AND.n5.EQ.1.AND.n6.EQ.1.AND.n7.EQ.0.AND.n8.EQ.0)THEN
845  IF(eltypeid(id).EQ.8)THEN
846  nnd1 = lmelv_prmry(1,id)
847  nnd2 = lmelv_prmry(2,id)
848  nnd3 = lmelv_prmry(6,id)
849  nnd4 = lmelv_prmry(5,id)
850  itmp = itmp + 1
851  ifaceid = 3
852  ENDIF
853  ELSE IF(n1.EQ.0.AND.n2.EQ.1.AND.n3.EQ.1.AND.n4.EQ.0 &
854  .AND.n5.EQ.0.AND.n6.EQ.1.AND.n7.EQ.1.AND.n8.EQ.0)THEN
855  IF(eltypeid(id).EQ.8)THEN
856  nnd1 = lmelv_prmry(2,id)
857  nnd2 = lmelv_prmry(3,id)
858  nnd3 = lmelv_prmry(7,id)
859  nnd4 = lmelv_prmry(6,id)
860  itmp = itmp + 1
861  ifaceid = 4
862  ENDIF
863  ELSE IF(n1.EQ.0.AND.n2.EQ.0.AND.n3.EQ.1.AND.n4.EQ.1 &
864  .AND.n5.EQ.0.AND.n6.EQ.0.AND.n7.EQ.1.AND.n8.EQ.1)THEN
865  IF(eltypeid(id).EQ.8)THEN
866  nnd1 = lmelv_prmry(3,id)
867  nnd2 = lmelv_prmry(4,id)
868  nnd3 = lmelv_prmry(8,id)
869  nnd4 = lmelv_prmry(7,id)
870  itmp = itmp + 1
871  ifaceid = 5
872  ENDIF
873  ELSE IF(n1.EQ.1.AND.n2.EQ.0.AND.n3.EQ.0.AND.n4.EQ.1 &
874  .AND.n5.EQ.1.AND.n6.EQ.0.AND.n7.EQ.0.AND.n8.EQ.1)THEN
875  IF(eltypeid(id).EQ.8)THEN
876  nnd1 = lmelv_prmry(5,id)
877  nnd2 = lmelv_prmry(8,id)
878  nnd3 = lmelv_prmry(4,id)
879  nnd4 = lmelv_prmry(1,id)
880  itmp = itmp + 1
881  ifaceid = 6
882  ENDIF
883  ELSE
884  print*,'Error in pressure face numbering'
885  stop
886  ENDIF
887 
888 ! BC flags
889 ! ignitable (=1)
890 ! non-ignitable (=0)
891 ! noninteracting (=2)
892 
893 
894 ! 3-node triangle, (via 4-node tetrahedral)
895 
896  IF(eltypeid(id).EQ.4)THEN
897 
898  ALLOCATE(surfmesh_tri3_item)
899 
900  surfmesh_tri3_item%ElemData(1) = nnd1
901  surfmesh_tri3_item%ElemData(2) = nnd2
902  surfmesh_tri3_item%ElemData(3) = nnd3
903  surfmesh_tri3_item%ElemData(4) = id
904 
905  IF(intfaceflag.EQ.1)THEN ! Fluid Structure interaction, with burning
906  CALL add_surfmesh_tri3(surfmesh_tri3_item, surfmesh_tri3_sf_head, surfmesh_tri3_sf_tail)
907  numeltet2d(1,ip) = numeltet2d(1,ip) + 1
908 
909  ELSE IF(intfaceflag.EQ.2)THEN ! fluid Structure interaction, without burning
910  CALL add_surfmesh_tri3(surfmesh_tri3_item, surfmesh_tri3_sf_nonignt_head, surfmesh_tri3_sf_nonignt_tail)
911  numeltet2d(3,ip) = numeltet2d(3,ip) + 1
912  ELSE IF(intfaceflag.EQ.0)THEN ! No fluid structure interaction
913  CALL add_surfmesh_tri3(surfmesh_tri3_item, surfmesh_tri3_s_head, surfmesh_tri3_s_tail)
914  numeltet2d(2,ip) = numeltet2d(2,ip) + 1
915  ELSE IF(intfaceflag.EQ.10)THEN ! No fluid structure interaction for non-matching meshes
916  overlaymesh = .true.
917  surfmesh_tri3_item%ElemData(5) = ifaceid
918  CALL add_surfmesh_tri3(surfmesh_tri3_item, surfmesh_tri3_ov1_head, surfmesh_tri3_ov1_tail)
919  numeltet2d(4,ip) = numeltet2d(4,ip) + 1
920  ELSE IF(intfaceflag.EQ.100)THEN ! No fluid structure interaction for non-matching meshes
921  overlaymesh = .true.
922  surfmesh_tri3_item%ElemData(5) = ifaceid
923  CALL add_surfmesh_tri3(surfmesh_tri3_item, surfmesh_tri3_ov2_head, surfmesh_tri3_ov2_tail)
924  numeltet2d(5,ip) = numeltet2d(5,ip) + 1
925 
926  ENDIF
927  tet4 = .true.
928 
929 ! 6-node triangle, (via 10-node tetrahedral)
930 
931  ELSE IF(eltypeid(id).EQ.10)THEN
932 
933  ALLOCATE(surfmesh_tri6_item)
934 
935  surfmesh_tri6_item%ElemData(1) = nnd1
936  surfmesh_tri6_item%ElemData(2) = nnd2
937  surfmesh_tri6_item%ElemData(3) = nnd3
938  surfmesh_tri6_item%ElemData(4) = nnd4
939  surfmesh_tri6_item%ElemData(5) = nnd5
940  surfmesh_tri6_item%ElemData(6) = nnd6
941  surfmesh_tri6_item%ElemData(7) = id
942 
943  IF(intfaceflag.EQ.1)THEN
944  CALL add_surfmesh_tri6(surfmesh_tri6_item, surfmesh_tri6_sf_head, surfmesh_tri6_sf_tail)
945  numeltet2d(1,ip) = numeltet2d(1,ip) + 1
946  ELSEIF(intfaceflag.EQ.2)THEN
947  CALL add_surfmesh_tri6(surfmesh_tri6_item, surfmesh_tri6_sf_nonignt_head, surfmesh_tri6_sf_nonignt_tail)
948  numeltet2d(3,ip) = numeltet2d(3,ip) + 1
949  ELSE IF(intfaceflag.EQ.0) THEN
950  CALL add_surfmesh_tri6(surfmesh_tri6_item, surfmesh_tri6_s_head, surfmesh_tri6_s_tail)
951  numeltet2d(2,ip) = numeltet2d(2,ip) + 1
952  ENDIF
953  tet10 = .true.
954 
955 ! 4-node quad, (via 8-node hexahedral)
956 
957  ELSE IF(eltypeid(id).EQ.8)THEN
958 
959  ALLOCATE(surfmesh_hex8_item)
960 
961  surfmesh_hex8_item%ElemData(1) = nnd1
962  surfmesh_hex8_item%ElemData(2) = nnd2
963  surfmesh_hex8_item%ElemData(3) = nnd3
964  surfmesh_hex8_item%ElemData(4) = nnd4
965  surfmesh_hex8_item%ElemData(5) = id
966  IF(intfaceflag.EQ.1)THEN
967  CALL add_surfmesh_hex8(surfmesh_hex8_item, surfmesh_hex8_sf_head, surfmesh_hex8_sf_tail)
968  numelhex2d(1,ip) = numelhex2d(1,ip) + 1
969  ELSE IF(intfaceflag.EQ.2)THEN
970  CALL add_surfmesh_hex8(surfmesh_hex8_item, surfmesh_hex8_sf_nonignt_head, surfmesh_hex8_sf_nonignt_tail)
971  numelhex2d(3,ip) = numelhex2d(3,ip) + 1
972  ELSE IF(intfaceflag.EQ.0) THEN
973  CALL add_surfmesh_hex8(surfmesh_hex8_item, surfmesh_hex8_s_head, surfmesh_hex8_s_tail)
974  numelhex2d(2,ip) = numelhex2d(2,ip) + 1
975  ELSE
976  print*,'ERROR, interface flag type not found',intfaceflag
977  stop
978  ENDIF
979 
980  hex8 = .true.
981  ENDIF
982 
983 
984 ! numel_2d(ip,IntFaceFlag) = numel_2d(ip,IntFaceFlag) + 1
985 
986 
987  ELSE IF(itype .EQ. 8)THEN ! boundary conditions
988  id = id + accumnd
989 !
990 ! CID = Coordinate frame ID
991 ! ICOMP = 6 displacement component flags (0 or 1)
992 ! note the flag is passed to node number one (i.e. fixed displacement)
993 
994  READ(iunit,'(I8,6I1)') iaux, disflag(1:6)
995  numdisflag = sum(disflag(1:6))
996 
997 
998  numserbc = numserbc + numdisflag
999 
1000  READ(iunit,*) tmpval(1:numdisflag)
1001 
1002  icnt = 0
1003  do i = 1, 6
1004  IF(disflag(i).eq.1)THEN
1005  icnt = icnt + 1
1006  disflagvalue(i) = tmpval(icnt)
1007  endif
1008  enddo
1009 
1010  IF(icnt.NE.numdisflag)THEN
1011  print*,'ERROR in processing boundary conditions'
1012  stop
1013  ENDIF
1014 
1015 ! add to the number of boundary conditions per processor
1016 
1017  IF(disflag(1).eq.1 )THEN ! structural boundary condition
1018  DO i = 1,numprocpernd(id)
1019  procid = procndlist(id,i)
1020  numbc_structural(procid) = numbc_structural(procid) + 1
1021  IF(bc_flag(1,id).EQ.0) numbc_flag(procid) = numbc_flag(procid) + 1
1022  ENDDO
1023 
1024  bc_flag(1,id) = bc_flag(1,id) + int(disflagvalue(1))
1025 
1026  maxnumbc_str = max(maxnumbc_str,int(disflagvalue(1)))
1027  endif
1028 
1029  IF(disflag(2).eq.1 )THEN ! temperature boundary condition
1030  DO i = 1,numprocpernd(id)
1031  procid = procndlist(id,i)
1032  numbc_thermal(procid) = numbc_thermal(procid) + 1
1033  IF(bc_flag(2,id).EQ.0) numbc_flag(procid) = numbc_flag(procid) + 1
1034  enddo
1035 
1036  bc_flag(2,id) = bc_flag(2,id) + 100*int(disflagvalue(2))
1037 
1038  maxnumbc_th = max(maxnumbc_th,int(disflagvalue(2)))
1039  endif
1040 
1041 
1042  IF(disflag(3).eq.1 )THEN ! mesh motion boundary condition
1043  DO i = 1,numprocpernd(id)
1044  procid = procndlist(id,i)
1045  numbc_meshmotion(procid) = numbc_meshmotion(procid) + 1
1046  IF(bc_flag(3,id).EQ.0) numbc_flag(procid) = numbc_flag(procid) + 1
1047  ENDDO
1048  bc_flag(3,id) = bc_flag(3,id) + 10000*int(disflagvalue(3))
1049 
1050  maxnumbc_mm = max(maxnumbc_mm,int(disflagvalue(3)))
1051  endif
1052 
1053 
1054 
1055  ELSE IF(itype .EQ. 7)THEN ! mesh motion boundary conditions
1056  id = id + accumnd
1057 !
1058 ! CID = Coordinate frame ID
1059 ! ICOMP = 6 displacement component flags (0 or 1)
1060 ! note the flag is passed to node number one (i.e. fixed displacement)
1061 
1062  READ(iunit,'()')
1063  READ(iunit,*) value
1064 
1065 ! ALLOCATE(BC_meshmotion_item)
1066 
1067 ! BC_meshmotion_item%BC_nodeGlb = id
1068 ! BC_meshmotion_item%BC_flagGlb = INT(value)
1069 
1070 ! CALL add_BC(BC_meshmotion_item, BC_meshmotion_head, BC_meshmotion_tail)
1071 
1072 
1073 ! add to the number of boundary conditions per processor
1074 
1075  DO i = 1,numprocpernd(id)
1076  procid = procndlist(id,i)
1077  numbc_meshmotion(procid) = numbc_meshmotion(procid) + 1
1078  IF(bc_flag(3,id).EQ.0) numbc_flag(procid) = numbc_flag(procid) + 1
1079  ENDDO
1080 
1081  bc_flag(3,id) = bc_flag(3,id) + 10000*int(value)
1082 
1083  maxnumbc_mm = max(maxnumbc_mm,int(value))
1084 
1085  ELSE IF(itype .EQ. 5)THEN ! coordinate frames
1086  READ(iunit,'()')
1087  READ(iunit,'()')
1088  READ(iunit,'()')
1089  READ(iunit,'()')
1090  ELSE IF(itype .EQ. 10)THEN ! nodal temperature (corners)
1091  id = id + accumnd
1092  READ(iunit,*) value
1093 
1094 ! ALLOCATE(BC_thermal_item)
1095 
1096 ! BC_thermal_item%BC_nodeGlb = id
1097 ! BC_thermal_item%BC_flagGlb = INT(value)
1098 
1099 ! CALL add_BC(BC_thermal_item, BC_thermal_head, BC_thermal_tail)
1100 
1101 ! add to the number of boundary conditions per processor
1102 
1103  DO i = 1,numprocpernd(id)
1104  procid = procndlist(id,i)
1105  numbc_thermal(procid) = numbc_thermal(procid) + 1
1106  IF(bc_flag(2,id).EQ.0) numbc_flag(procid) = numbc_flag(procid) + 1
1107  ENDDO
1108 
1109  bc_flag(2,id) = bc_flag(2,id) + 100*int(value)
1110 
1111  maxnumbc_th = max(maxnumbc_th,int(value))
1112 
1113  ELSE
1114  DO i = 1, kc
1115  READ(iunit,'()')
1116  ENDDO
1117  ENDIF
1118  ENDDO
1119 
1120  accumel = sum(numel_glb(1:ibody))
1121 
1122  accumnd = sum(numnp_glb(1:ibody))
1123  ENDDO
1124 
1125 ! if negative number then higher order element
1126 
1127 
1128  IF(tet4.AND..NOT.(tet10).AND..NOT.(hex8))THEN
1129  meshtype2d = 3
1130  ELSE IF (.NOT.(tet4).AND.tet10.AND..NOT.(hex8))THEN
1131  meshtype2d = 6
1132  ELSE IF (.NOT.(tet4).AND..NOT.(tet10).AND.hex8)THEN
1133  meshtype2d = 4
1134  ELSE
1135  meshtype2d = 5
1136  ENDIF
1137 
1138 ! PRINT*,'Number of Surface elements, Interacting with burning =', NumEltet2D(1,:)
1139 ! PRINT*,'Number of Surface elements, Interacting with Non-burning =', NumEltet2D(3,:)
1140 ! PRINT*,'Number of Surface elements, Non-Interacting =', NumEltet2D(2,:)
1141 
1142  print*,'BOUNDARY CONDITIONS'
1143  print*,' Total of all types = ',numserbc
1144  print*,' Number of structural = ',maxnumbc_str
1145  print*,' Number of meshmotion = ',maxnumbc_mm
1146  print*,' Number of thermal = ',maxnumbc_th
1147 
1148  IF(numvertx.EQ.4)THEN
1149  numvertx2d = 3
1150  ELSE IF(numvertx.EQ.10)THEN
1151  numvertx2d = 6
1152  ELSE IF(numvertx.EQ.8)THEN
1153  numvertx2d = 4
1154  ENDIF
1155 
1156  DO ibody = 1, numgeombodies
1157  iunit = 100 + ibody
1158  CLOSE(iunit)
1159  enddo
1160 
1161  RETURN
1162 
1163 END SUBROUTINE read_patran
1164 
1165 
subroutine add_surfmesh_tri6(new, head, tail)
**********************************************************************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 kc
size_t value()
Returns an index corresponding to a free vertex.
Tfloat sum() const
Return the sum of all the pixel values in an image.
Definition: CImg.h:13022
subroutine newcommlist(NumEl, NumNP, NumProcs, NumVertex, NodeConn, ElPart, NumProcPerNd, ProcNdList, MaxNumberOfProcsToShareNode, NumElPerProc, NumNdPerProc)
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
double sqrt(double d)
Definition: double.h:73
subroutine add_surfmesh_tri3(new, head, tail)
blockLoc i
Definition: read.cpp:79
subroutine read_patran(numvertx2d, dhmin, nprocs)
**********************************************************************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 form
virtual std::ostream & print(std::ostream &os) const
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
j indices j
Definition: Indexing.h:6
unsigned long id(const Leda_like_handle &x)
Definition: Handle.h:107
subroutine add_surfmesh_hex8(new, head, tail)