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

Go to the source code of this file.

Functions/Subroutines

subroutine i24setnodes (ipari, intbuf_tab, intercep, itab, i24maxnsne)
integer function secnd_surface_on_domain (intercep, se, proc)

Function/Subroutine Documentation

◆ i24setnodes()

subroutine i24setnodes ( integer, dimension(npari,*) ipari,
type(intbuf_struct_), dimension(*) intbuf_tab,
type(intersurfp), dimension(3,ninter) intercep,
integer, dimension(*) itab,
integer i24maxnsne )

Definition at line 37 of file i24setnodes.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE message_mod
42 USE i7i10splitmod
43 USE front_mod
44 USE intbufdef_mod
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C G l o b a l P a r a m e t e r s
51C-----------------------------------------------
52#include "param_c.inc"
53C-----------------------------------------------
54C C o m m o n B l o c k s
55C-----------------------------------------------
56#include "com04_c.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 INTEGER IPARI(NPARI,*),ITAB(*),I24MAXNSNE
61 TYPE(INTERSURFP) :: INTERCEP(3,NINTER)
62 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
63C-----------------------------------------------
64C F u n c t i o n
65C-----------------------------------------------
66 INTEGER NLOCAL
67 EXTERNAL nlocal
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER ITY,NRTM,N,IED,N1,N2,N3,N4,NRTSE,NSNE
72 INTEGER S1,S2,P1,P2,PP,NEXT,POS
73 INTEGER NI,K,I,PROC,KM1(4),KM2(4),PROC0,IEDGE4
74 DATA km1/1,2,3,4/
75 DATA km2/2,3,4,1/
76 INTEGER INTERSURFL
77 EXTERNAL intersurfl
78C--------------------------------------------------------------
79 i24maxnsne = 0
80 DO ni=1,ninter
81
82 ity = ipari(7,ni)
83 iedge4 = ipari(59,ni)
84 IF (ity==24)THEN
85
86C First set SECONDARY surface to avoid issues : Same SECONDARY surface not on same
87C domain than MAIN surface
88 nrtse = ipari(52,ni)
89 nsne = ipari(55,ni)
90 i24maxnsne = max(i24maxnsne,nsne)
91 IF (iedge4 > 0 ) THEN
92 IF (.NOT.(ASSOCIATED(intercep(2,ni)%P)))THEN
93C In Type24 INTERCEP(2 gives Edge MPI Domain
94 ALLOCATE(intercep(2,ni)%P(nrtse))
95 ENDIF
96C
97 DO i=1,nrtse
98 n1= intbuf_tab(ni)%IRTSE((i-1)*5+1)
99 n2= intbuf_tab(ni)%IRTSE((i-1)*5+2)
100 n3= intbuf_tab(ni)%IRTSE((i-1)*5+3)
101 n4= intbuf_tab(ni)%IRTSE((i-1)*5+4)
102
103 proc = intersurfl(n1,n2,n3,n4)
104
105 intercep(2,ni)%P(i)=proc
106 ENDDO
107 ENDIF
108
109
110 nrtm = ipari(4,ni)
111 DO k=1,nrtm
112 proc = intercep(1,ni)%P(k)
113 IF(proc==0)THEN
114 CALL ancmsg(msgid=978,
115 . msgtype=msgerror,
116 . anmode=anstop,
117 . i1=ipari(15,ni))
118 ELSE
119 DO i=1,8
120 n = iabs(intbuf_tab(ni)%NVOISIN((k-1)*8+i))
121 IF(n /=0) THEN
122 CALL ifrontplus(n,proc)
123 ENDIF
124 ENDDO
125 END IF
126 ENDDO
127
128
129 ENDIF
130 ENDDO
integer function nlocal(n, p)
Definition ddtools.F:349
integer function intersurfl(n1, n2, n3, n4)
Definition ddtools.F:1054
subroutine ifrontplus(n, p)
Definition frontplus.F:100
#define max(a, b)
Definition macros.h:21
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889

◆ secnd_surface_on_domain()

integer function secnd_surface_on_domain ( type(intersurfp) intercep,
integer se,
integer proc )

Definition at line 142 of file i24setnodes.F.

143C-----------------------------------------------
144C M o d u l e s
145C-----------------------------------------------
146 USE front_mod
147 USE intbufdef_mod
148C-----------------------------------------------
149C I m p l i c i t T y p e s
150C-----------------------------------------------
151#include "implicit_f.inc"
152C-----------------------------------------------
153C D u m m y A r g u m e n t s
154C-----------------------------------------------
155 TYPE(INTERSURFP) :: INTERCEP
156 INTEGER SE,PROC
157C-----------------------------------------------
158C L o c a l V a r i a b l e s
159C-----------------------------------------------
160 INTEGER NEXT,P
161C-----------------------------------------------
163
164 p= intercep%P(2+2*(se-1)+1)
165 next=intercep%P(2+2*(se-1)+2)
166
167 IF (p==proc)THEN
169 RETURN
170 ENDIF
171
172 DO WHILE(p/=proc.AND.next/=-1)
173 p=intercep%P(2+2*(next-1)+1)
174 next = intercep%P(2+2*(next-1)+2)
175 ENDDO
176
177 IF(p==proc)THEN
179 ENDIF
180
181 RETURN
182
integer function secnd_surface_on_domain(intercep, se, proc)