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

Go to the source code of this file.

Functions/Subroutines

subroutine crk_tagxp3 (iparg, ixtg, nft, jft, jlt, elcutc, iad_crktg, iel_crktg, inod_crk, enrtag, nxlay, crkedge, xedge3n, itab)

Function/Subroutine Documentation

◆ crk_tagxp3()

subroutine crk_tagxp3 ( integer, dimension(nparg,*) iparg,
integer, dimension(nixtg,*) ixtg,
integer nft,
integer jft,
integer jlt,
integer, dimension(2,*) elcutc,
integer, dimension(3,*) iad_crktg,
integer, dimension(*) iel_crktg,
integer, dimension(*) inod_crk,
integer, dimension(numnod,*) enrtag,
integer nxlay,
type (xfem_edge_), dimension(*) crkedge,
integer, dimension(3,*) xedge3n,
integer, dimension(numnod) itab )

Definition at line 31 of file crk_tagxp3.F.

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 NFT,JFT,JLT,NXLAY
54 INTEGER IPARG(NPARG,*),IXTG(NIXTG,*),ELCUTC(2,*),INOD_CRK(*),
55 . IAD_CRKTG(3,*),XEDGE3N(3,*),IEL_CRKTG(*),ENRTAG(NUMNOD,*),ITAB(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,IR,ELCRK,ELCRKTG,ILEV,ILAY,IXEL,ELCUT,IECUT,NELCRK,NSX,
61 . IED,EDGE,FAC,IBOUNDEDGE,LAYCUT,ENR0,ENR,ITRI,ITIP,IAD,COUNT
62 INTEGER JCT(MVSIZ),IADC(3),NS(3)
63C=======================================================================
64 nelcrk = 0
65 DO i=jft,jlt
66 jct(i) = 0
67 IF (elcutc(1,i+nft) /= 0) THEN
68 nelcrk = nelcrk + 1
69 jct(nelcrk) = i
70 ENDIF
71 ENDDO
72 IF (nelcrk == 0) RETURN
73C
74 DO ilay=1,nxlay
75 DO ixel=1,nxel
76 ilev = nxel*(ilay-1) + ixel
77 DO ir=1,nelcrk
78 i = jct(ir)
79 elcrktg = iel_crktg(i+nft)
80 elcrk = elcrktg + ecrkxfec
81 elcut = xfem_phantom(ilay)%ELCUT(elcrk)
82 IF (elcut /= 0) THEN
83 ns(1) = ixtg(2,i+nft)
84 ns(2) = ixtg(3,i+nft)
85 ns(3) = ixtg(4,i+nft)
86 iadc(1) = iad_crktg(1,elcrktg)
87 iadc(2) = iad_crktg(2,elcrktg)
88 iadc(3) = iad_crktg(3,elcrktg)
89 itri = xfem_phantom(ilay)%ITRI(1,elcrk)
90 laycut = crkedge(ilay)%LAYCUT(elcrk)
91c---------------------------------------
92 IF (abs(laycut) == 1) THEN
93c new advancing crack
94c Tag phantom nodes with positive enrichment to copy the velocities
95c---------------------------------------
96 IF (ixel == 3) THEN ! sender
97 DO k=1,3
98 iad = iadc(k)
99 enr0 = crklvset(ilev)%ENR0(2,iad)
100 enr = crklvset(ilev)%ENR0(1,iad)
101 edge = xedge3n(k,elcrktg) ! global egdge N
102 iboundedge = crkedge(ilay)%IBORDEDGE(edge)
103 nsx = inod_crk(ns(k))
104 IF (enr > 0 .and. iboundedge /= 2) THEN
105 xfem_phantom(ilay)%TAGXP(1,nsx,enr) = iad
106 xfem_phantom(ilay)%TAGXP(2,nsx,enr) = ilev
107 xfem_phantom(ilay)%TAGXP(3,nsx,enr) = 2 ! counter
108 ENDIF
109 ENDDO
110 ELSE ! receiver
111 DO k=1,3
112 iad = iadc(k)
113 enr0 = crklvset(ilev)%ENR0(2,iad)
114 enr = abs(crklvset(ilev)%ENR0(1,iad))
115 edge = xedge3n(k,elcrktg) ! global egdge N
116 iboundedge = crkedge(ilay)%IBORDEDGE(edge)
117 nsx = inod_crk(ns(k))
118 IF (enr > 0 .and. iboundedge /= 2) THEN
119 xfem_phantom(ilay)%TAGXP(4,nsx,enr) = iad
120 xfem_phantom(ilay)%TAGXP(5,nsx,enr) = ilev
121 xfem_phantom(ilay)%TAGXP(3,nsx,enr) = 2 ! counter
122 ENDIF
123 ENDDO
124 ENDIF
125 ENDIF ! LAYCUT = 1
126C--------------------------------------------------------------------------
127 ENDIF ! IF(ELCUT /= 0)THEN
128 ENDDO ! DO IR=1,NELCRK
129 ENDDO ! DO IXEL=1,NXEL
130 ENDDO ! DO ILAY=1,NXLAY
131C-----------------------------------------------
132 RETURN
type(xfem_phantom_), dimension(:), allocatable xfem_phantom
type(xfem_lvset_), dimension(:), allocatable crklvset