OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c_ncrkxfem.F File Reference
#include "implicit_f.inc"
#include "com_xfem1.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine c_ncrkxfem (nodglob, inod_crkxfem, inod_l, numnod_l, numnodcrkxfe_l, index, proc, ixc, ixtg, cep_xfe, nodlocal, nodlevxf_l, nodlevxf, nodglobxfe, nod_xfe_l, crkshell)

Function/Subroutine Documentation

◆ c_ncrkxfem()

subroutine c_ncrkxfem ( integer, dimension(*) nodglob,
integer, dimension(*) inod_crkxfem,
integer, dimension(*) inod_l,
integer numnod_l,
integer numnodcrkxfe_l,
integer, dimension(*) index,
integer proc,
integer, dimension(nixc,*) ixc,
integer, dimension(nixtg,*) ixtg,
integer, dimension(*) cep_xfe,
integer, dimension(*) nodlocal,
integer, dimension(*) nodlevxf_l,
integer, dimension(*) nodlevxf,
integer, dimension(*) nodglobxfe,
integer nod_xfe_l,
type (xfem_shell_), dimension(nlevmax) crkshell )

Definition at line 29 of file c_ncrkxfem.F.

33C-----------------------------------------------
34 USE xfem2def_mod
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C C o m m o n B l o c k s
41C-----------------------------------------------
42#include "com_xfem1.inc"
43#include "com04_c.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER NODGLOB(*),INOD_CRKXFEM(*),INOD_L(*),
48 . NUMNOD_L,NUMNODCRKXFE_L,INDEX(*),PROC,
49 . IXC(NIXC,*),IXTG(NIXTG,*),CEP_XFE(*),
50 . NODLOCAL(*),NODLEVXF_L(*),NODLEVXF(*),
51 . NODGLOBXFE(*),NOD_XFE_L
52 TYPE (XFEM_SHELL_) , DIMENSION(NLEVMAX) :: CRKSHELL
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I,NL_L,II,JJ,J,K,NOD,ELTYP,ELEM,
57 . INOD_CRK,NOD_XFE_G,NELCRK
58 INTEGER, DIMENSION(:), ALLOCATABLE :: NODTAG
59C=======================================================================
60! 1d array
61 ALLOCATE( nodtag(0:numnod_l+1) )
62! ----------------------------------
63c Tableaux noeuds phantomes chaque ply
64C-----------------------------------------------
65 nelcrk = 0
66 DO k=1,nlevmax
67 DO i=1,crkshell(k)%CRKNUMSHELL
68 elem = crkshell(k)%PHANTOML(i)
69 eltyp = crkshell(k)%ELTYPE(i)
70 IF (cep_xfe(i) == proc) THEN
71 IF(eltyp == 4) THEN
72 DO j=1,eltyp
73 nod = ixc(j+1,elem)
74 IF (nod > 0) THEN
75 IF (inod_crkxfem(nod) > 0) THEN ! N noeud local xfem
76 nod_xfe_g = crkshell(k)%XNODEG(j,i) ! ID glob node phantome sur ply
77 nod_xfe_l = nod_xfe_l + 1 ! ID local node phantome sur ply
78 nodglobxfe(nod_xfe_l) = nod_xfe_g ! Id local -> Id global (phant)
79 ENDIF
80 ENDIF
81 ENDDO
82 ELSEIF (eltyp == 3) THEN
83 DO j=1,eltyp
84 nod = ixtg(j+1,elem)
85 IF (nod > 0) THEN
86 IF(inod_crkxfem(nod) > 0)THEN
87 nod_xfe_g = crkshell(k)%XNODEG(j,i)
88 nod_xfe_l = nod_xfe_l + 1
89 nodglobxfe(nod_xfe_l) = nod_xfe_g
90 ENDIF
91 ENDIF
92 ENDDO
93C
94c add one more node (as sh4) for animation files (3N -> 4N)
95C
96 nod_xfe_g = crkshell(k)%XNODEG(4,i)
97 nod_xfe_l = nod_xfe_l + 1
98 nodglobxfe(nod_xfe_l) = nod_xfe_g
99 END IF
100 ENDIF
101 ENDDO
102 nelcrk = nelcrk + crkshell(k)%CRKNUMSHELL ! Nb elements total sur nlevmax
103 ENDDO
104 numnodxfe = nod_xfe_l ! Nb noeuds total sur nlevmax
105C
106 nodtag(1:numnod_l) = 0
107 k = 1 ! the same as K=1,NLEVMAX
108 DO i=1,crkshell(k)%CRKNUMSHELL
109 eltyp = crkshell(k)%ELTYPE(i)
110 elem = crkshell(k)%PHANTOML(i)
111 IF (cep_xfe(i) == proc) THEN
112 IF (eltyp == 4) THEN
113 DO j=1,eltyp
114 nod = ixc(j+1,elem)
115 nodtag(nodlocal(nod))=nod
116 ENDDO
117 ELSEIF (eltyp == 3) THEN
118 DO j=1,eltyp
119 nod = ixtg(j+1,elem)
120 nodtag(nodlocal(nod))=nod
121 ENDDO
122 END IF
123 END IF
124 END DO
125C---
126 nl_l = 0
127 DO i=1,numnod_l
128 nod = nodtag(i)
129 IF (nod > 0) THEN
130 IF (inod_crkxfem(nod) > 0) THEN
131 nl_l = nl_l + 1
132 inod_l(i) = nl_l
133 index(nl_l) = inod_crkxfem(nod)
134 inod_crk = inod_crkxfem(nod)
135 nodlevxf_l(nl_l) = nodlevxf(inod_crk) ! nb des copies d'un nooeuds std xfem
136 ENDIF
137 ENDIF
138 ENDDO
139C---
140 numnodcrkxfe_l = nl_l
141C---
142! ----------------------------------
143! 1d array
144 DEALLOCATE( nodtag )
145! ----------------------------------
146 RETURN