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

Go to the source code of this file.

Functions/Subroutines

subroutine i25sto_edg (j_stok, irect, x, ii_stok, inacti, cand_s, cand_m, mulnsn, noint, marge, i_mem, prov_s, prov_m, igap0, cand_a, nedge, ledge, itab, drad, igap, gape, gap_e_l, admsr, edg_bisector, vtx_bisector, cand_p, dgapload)

Function/Subroutine Documentation

◆ i25sto_edg()

subroutine i25sto_edg ( integer j_stok,
integer, dimension(4,*) irect,
x,
integer ii_stok,
integer inacti,
integer, dimension(*) cand_s,
integer, dimension(*) cand_m,
integer mulnsn,
integer noint,
marge,
integer i_mem,
integer, dimension(mvsiz) prov_s,
integer, dimension(mvsiz) prov_m,
integer igap0,
integer, dimension(*) cand_a,
integer nedge,
integer, dimension(nledge,*) ledge,
integer, dimension(*) itab,
drad,
integer igap,
gape,
gap_e_l,
integer, dimension(4,*) admsr,
real*4, dimension(3,4,*) edg_bisector,
real*4, dimension(3,2,*) vtx_bisector,
cand_p,
intent(in) dgapload )

Definition at line 32 of file i25sto_edg.F.

39C============================================================================
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE tri7box
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C G l o b a l P a r a m e t e r s
50C-----------------------------------------------
51#include "mvsiz_p.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "param_c.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER I_MEM, IGAP0, NEDGE, NIN, ITAB(*), INACTI
60 INTEGER J_STOK,MULNSN,NOINT,IFORM,IGAP
61 INTEGER IRECT(4,*),LEDGE(NLEDGE,*),ADMSR(4,*),CAND_S(*),CAND_M(*),II_STOK,CAND_A(*)
62 INTEGER PROV_S(MVSIZ),PROV_M(MVSIZ)
64 . x(3,*), drad, marge, gape(*), gap_e_l(*), cand_p(*)
65 my_real , INTENT(IN) :: dgapload
66 real*4 edg_bisector(3,4,*), vtx_bisector(3,2,*)
67C-----------------------------------------------
68C L o c a l V a r i a b l e s
69C-----------------------------------------------
70 INTEGER I,J,K_STOK,I_STOK,IAD0,IAD,IADFIN,N,NE
71 INTEGER I_STOK_FIRST,NINDX,INDEX(MVSIZ)
72C REAL
74 . pene(mvsiz)
75C-----------------------------------------------
76 CALL i25pen3_edg( j_stok,prov_s ,prov_m ,drad ,igap0 ,
77 . nedge ,ledge ,marge ,gape ,gap_e_l ,
78 . igap ,x ,irect ,pene ,admsr ,
79 . edg_bisector,vtx_bisector ,itab,dgapload)
80C-----------------------------------------------
81C SUPPRESSION DES ANCIENS CANDIDATS DEJA STOCKES (PENE INITIALE)
82C-----------------------------------------------
83 IF(inacti==5)THEN
84 DO i=1,j_stok
85 IF(pene(i)/=zero)THEN
86 n = prov_s(i)
87 ne = prov_m(i)
88C IF(N>NEDGE) THEN
89C numerotation tris precedent pour les noeuds non locaux (SPMD)
90C N = OLDNUM(N-NEDGE)+NEDGE
91C IF(N==NEDGE) N = NEDGE+NEDGEROLD+1
92C END IF
93 j = cand_a(n)
94 DO WHILE(j<=cand_a(n+1)-1)
95 IF(cand_m(j)==ne)THEN
96 pene(i)=zero
97 j=cand_a(n+1)
98 ELSE
99 j=j+1
100 ENDIF
101 ENDDO
102 ENDIF
103 ENDDO
104 ENDIF
105C-----------------------------------------------
106 k_stok = 0
107 DO i=1,j_stok
108 IF(pene(i)/=zero) THEN
109 k_stok = k_stok + 1
110 END IF
111 ENDDO
112 IF(k_stok==0)RETURN
113C
114
115 i_stok = ii_stok
116 IF(i_stok+k_stok>mulnsn) THEN
117 i_mem = 2
118
119 RETURN
120 ENDIF
121 ii_stok = i_stok + k_stok
122
123 IF(inacti==5)THEN
124 DO i=1,j_stok
125 IF(pene(i)/=zero)THEN
126 i_stok = i_stok + 1
127 cand_s(i_stok) = prov_s(i)
128 cand_m(i_stok) = prov_m(i)
129 cand_p(i_stok) = zero
130 ENDIF
131 ENDDO
132 ELSE
133 DO i=1,j_stok
134 IF(pene(i)/=zero)THEN
135 i_stok = i_stok + 1
136 cand_s(i_stok) = prov_s(i)
137 cand_m(i_stok) = prov_m(i)
138 ENDIF
139 ENDDO
140 END IF
141C-----------------------------------------------
142 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine i25pen3_edg(jlt, cand_s, cand_m, drad, igap0, nedge, ledge, marge, gape, gap_e_l, igap, x, irect, pene, admsr, edg_bisector, vtx_bisector, itab, dgapload)
Definition i25pen3_edg.F:34