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

Go to the source code of this file.

Functions/Subroutines

subroutine upenr_crk (addcne_crk, inod_crk, nodft, nodlt, nodenr, enrtag, nodlevxf, procne_crk)

Function/Subroutine Documentation

◆ upenr_crk()

subroutine upenr_crk ( integer, dimension(*) addcne_crk,
integer, dimension(*) inod_crk,
integer nodft,
integer nodlt,
integer, dimension(*) nodenr,
integer, dimension(numnod,*) enrtag,
integer, dimension(*) nodlevxf,
integer, dimension(*) procne_crk )

Definition at line 30 of file upenr_crk.F.

32C-----------------------------------------------
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C C o m m o n B l o c k s
40C-----------------------------------------------
41#include "com04_c.inc"
42#include "com_xfem1.inc"
43C-----------------------------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER ADDCNE_CRK(*),INOD_CRK(*),NODFT,NODLT,NODENR(*),
47 . ENRTAG(NUMNOD,*),NODLEVXF(*),PROCNE_CRK(*)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER I,KK,N,NSX,NCT_CRK,NC_CRK,EN0,ENR,ILEV,NLEV,OK_UP,ENR_MAX
52 INTEGER, DIMENSION(:),ALLOCATABLE :: IFAC0
53C=======================================================================
54 ALLOCATE(ifac0(0:ienrnod))
55c
56 DO n = nodft,nodlt
57 nsx = inod_crk(n)
58 IF (nsx <= 0) cycle
59 ifac0 = 0
60 nct_crk = addcne_crk(nsx)-1
61 nc_crk = addcne_crk(nsx+1)-addcne_crk(nsx)
62 nlev = nodlevxf(nsx)
63 DO ilev=1,nlev
64 ok_up = 0
65 DO kk = nct_crk+1, nct_crk+nc_crk
66 en0 = abs(crklvset(ilev)%ENR0(1,kk))
67 IF (en0 > 0) THEN
68 enr_max = enrtag(n,en0)
69 IF (enr_max > 0) THEN ! il y a une fissure dans l'adresse sky
70 ifac0(en0) = enr_max
71 ok_up = 1
72 ENDIF
73 ENDIF
74 ENDDO
75c
76 IF (ok_up == 1) THEN
77 DO kk = nct_crk+1, nct_crk+nc_crk
78 en0 = abs(crklvset(ilev)%ENR0(1,kk))
79 enr = ifac0(en0)
80 IF (en0 > 0 .and. enr > 0) crklvset(ilev)%ENR0(1,kk) = enr
81 ENDDO
82 ENDIF
83 ENDDO ! ILEV=1,NLEV
84C
85 enrtag(n,1:ienrnod) = 0
86 ENDDO ! N = NODFT,NODLT
87c-----
88 DEALLOCATE(ifac0)
89C-----------
90 RETURN
type(xfem_lvset_), dimension(:), allocatable crklvset