OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
upenric1_n3.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23c
24!||====================================================================
25!|| upenric1_n3 ../engine/source/elements/xfem/upenric1_n3.F
26!||--- called by ------------------------------------------------------
27!|| upxfem1 ../engine/source/elements/xfem/upxfem1.F
28!||--- uses -----------------------------------------------------
29!|| crackxfem_mod ../engine/share/modules/crackxfem_mod.F
30!||====================================================================
31 SUBROUTINE upenric1_n3(IPARG ,IXTG ,NFT ,JFT ,JLT ,
32 . ELCUTC ,IAD_CRKTG,IEL_CRKTG ,INOD_CRK,NXLAY ,
33 . NODEDGE,ENRTAG ,CRKEDGE ,XEDGE3N )
34C-----------------------------------------------
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C C o m m o n B l o c k s
46C-----------------------------------------------
47#include "com04_c.inc"
48#include "com_xfem1.inc"
49#include "param_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER IPARG(NPARG,*),IXTG(NIXTG,*),NFT,JFT,JLT,NXLAY,
54 . ELCUTC(2,*),IAD_CRKTG(3,*),XEDGE3N(3,*),IEL_CRKTG(*),
55 . inod_crk(*),nodedge(2,*),enrtag(numnod,*)
56 TYPE (XFEM_EDGE_) , DIMENSION(*) :: CRKEDGE
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I,K,II,ELCRK,ILEV,LAYCUT,IECUT,ILAY,IXEL,
61 . IR,NELCRK,EDGE,IADC1,IADC2,IADC3,NOD1,NOD2,ELCRKTG,IED,
62 . ie10,ie20,ie1,ie2,k1,k2,en1,en2,en3
63 INTEGER JCT(MVSIZ),ENR0(3),NS(3),D(3)
64 DATA d/2,3,1/
65C=======================================================================
66 ir = 0
67 DO i=jft,jlt
68 jct(i) = 0
69 IF (elcutc(1,i+nft) /= 0) THEN
70 ir = ir + 1
71 jct(ir) = i
72 ENDIF
73 ENDDO
74C---
75 nelcrk = ir
76 IF (nelcrk == 0) RETURN
77C---
78 DO ilay=1,nxlay
79 ii = nxel*(ilay-1)
80 DO ir=1,nelcrk
81 i = jct(ir)
82 elcrktg = iel_crktg(i+nft)
83 elcrk = elcrktg + ecrkxfec
84 laycut = crkedge(ilay)%LAYCUT(elcrk)
85 IF (laycut /= 0) THEN
86 iadc1 = iad_crktg(1,elcrktg)
87 iadc2 = iad_crktg(2,elcrktg)
88 iadc3 = iad_crktg(3,elcrktg)
89 ns(1) = ixtg(2,i+nft)
90 ns(2) = ixtg(3,i+nft)
91 ns(3) = ixtg(4,i+nft)
92c
93 DO ixel=1,nxel
94 ilev = ii+ixel
95 enr0(1) = 0
96 enr0(2) = 0
97 enr0(3) = 0
98 en1 = crklvset(ilev)%ENR0(1,iadc1)
99 en2 = crklvset(ilev)%ENR0(1,iadc2)
100 en3 = crklvset(ilev)%ENR0(1,iadc3)
101 IF (en1 /= 0) enr0(1) = en1
102 IF (en2 /= 0) enr0(2) = en2
103 IF (en3 /= 0) enr0(3) = en3
104c
105 DO k=1,3
106 edge = xedge3n(k,elcrktg)
107 ied = crkedge(ilay)%IEDGETG(k,elcrktg)
108 iecut = crkedge(ilay)%ICUTEDGE(edge)
109 ie1 = 0
110 ie2 = 0
111 IF (iecut == 3 .AND. ied > 0) THEN ! connection edge
112 nod1 = nodedge(1,edge)
113 nod2 = nodedge(2,edge)
114 ie10 = crkedge(ilay)%EDGEENR(1,edge)
115 ie20 = crkedge(ilay)%EDGEENR(2,edge)
116 IF (nod1 == ixtg(k+1,i+nft) .and.
117 . nod2 == ixtg(d(k)+1,i+nft)) THEN
118 k1 = k
119 k2 = d(k)
120 ie1 = enr0(k)
121 ie2 = enr0(d(k))
122 ELSE IF (nod2 == ixtg(k+1,i+nft) .and.
123 . nod1 == ixtg(d(k)+1,i+nft)) THEN
124 k1 = d(k)
125 k2 = k
126 ie1 = enr0(d(k))
127 ie2 = enr0(k)
128 ENDIF
129c
130c set ENRTAG for nodal enrichment update
131 IF(ie1 /= 0) enrtag(ns(k1),abs(ie1))
132 . = max(enrtag(ns(k1),abs(ie1)),ie10)
133 IF(ie2 /= 0) enrtag(ns(k2),abs(ie2))
134 . = max(enrtag(ns(k2),abs(ie2)),ie20)
135c
136 ENDIF ! IF(IECUT == 3)THEN
137 ENDDO ! DO K=1,3
138 ENDDO ! IXEL=1,NXEL
139 ENDIF ! IF(LAYCUT /= 0)THEN
140 ENDDO ! DO IR=1,NELCRK
141 ENDDO ! DO ILAY=1,NXLAY
142C-----------------------------------------------
143 RETURN
144 END
#define max(a, b)
Definition macros.h:21
type(xfem_lvset_), dimension(:), allocatable crklvset
subroutine upenric1_n3(iparg, ixtg, nft, jft, jlt, elcutc, iad_crktg, iel_crktg, inod_crk, nxlay, nodedge, enrtag, crkedge, xedge3n)
Definition upenric1_n3.F:34