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

Go to the source code of this file.

Functions/Subroutines

subroutine iwcontdd_type24 (numnod, nsn, nmn, nsv, msr, iwcont, nsnt, nmnt, intbuf_tab)

Function/Subroutine Documentation

◆ iwcontdd_type24()

subroutine iwcontdd_type24 ( integer, intent(in) numnod,
integer, intent(in) nsn,
integer, intent(in) nmn,
integer, dimension(nsn), intent(in) nsv,
integer, dimension(nmn), intent(in) msr,
integer, dimension(5,numnod), intent(inout) iwcont,
integer, intent(inout) nsnt,
integer, intent(inout) nmnt,
type(intbuf_struct_), intent(in) intbuf_tab )
Parameters
[in]numnodnumber nodes
[in]nsnnumber of S nodes
[in]nmnnumber of M nodes
[in]nsvlist of S nodes
[in]msrlist of M nodes
[in,out]nsnttotal number of S node for all interfaces
[in,out]nmnttotal number of M node for all interfaces
[in]intbuf_tabinterface structure

Definition at line 31 of file iwcontdd_type24.F.

32!$COMMENT
33! IWCONTDD_TYPE24 description :
34! update the weight of nodes belonging to an interface type 24
35! to balance the sorting of the engine
36!
37! IWCONTDD_TYPE24 organization :
38! for S node :
39! * check if the node is a real node or a "fictive node"
40! * for "fictive" node --> find the id of the 2 real nodes
41! * add the weight to the S node
42! for M node :
43! * add the weight to the M node
44!$ENDCOMMENT
45 USE intbufdef_mod
46C-----------------------------------------------
47C I m p l i c i t T y p e s
48C-----------------------------------------------
49#include "implicit_f.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER, INTENT(in) :: NUMNOD !< number nodes
54 INTEGER, INTENT(in) :: NSN !< number of S nodes
55 INTEGER, INTENT(in) :: NMN !< number of M nodes
56 INTEGER, DIMENSION(NSN), INTENT(in) :: NSV !< list of S nodes
57 INTEGER, DIMENSION(NMN), INTENT(in) :: MSR !< list of M nodes
58 INTEGER, DIMENSION(5,NUMNOD), INTENT(inout) :: IWCONT ! weight array for the interface
59 INTEGER, INTENT(inout) :: NSNT !< total number of S node for all interfaces
60 INTEGER, INTENT(inout) :: NMNT !< total number of M node for all interfaces
61 TYPE(INTBUF_STRUCT_), INTENT(in) :: INTBUF_TAB !< interface structure
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER :: I
66 INTEGER :: S_NODE_ID,M_NODE_ID,S_NODE_ID_2
67 INTEGER :: NODE_ID_1,NODE_ID_2 ! id of the 2 nodes of the edge for type 24 with edge to edge
68 INTEGER :: SEGMENT_ID_TYPE24
69C-----------------------------------------------
70
71 ! ---------------------------
72 ! loop over the S nodes
73 DO i = 1,nsn
74 s_node_id = nsv(i)
75
76 s_node_id_2 = 0
77 ! -------------
78 ! interface 24 : secondary node can be "fictive" node (ID > numnod)
79 ! a fictive node is the barycentre of an edge
80 ! --> the weight is added to the first node of the edge
81 IF (s_node_id >numnod) THEN
82 s_node_id = s_node_id - numnod
83 CALL i24fic_getn(s_node_id,intbuf_tab%IRTSE,intbuf_tab%IS2SE,segment_id_type24,node_id_1,node_id_2)
84 s_node_id = node_id_1 ! add the weight to the first node of the edge
85 s_node_id_2 = node_id_2 ! add the weight to the second node of the edge
86 ENDIF
87 ! -------------
88
89 iwcont(1,s_node_id) = iwcont(1,s_node_id)+1
90 nsnt = nsnt + 1
91 IF(s_node_id_2/=0) THEN
92 iwcont(1,s_node_id_2) = iwcont(1,s_node_id_2)+1
93 nsnt = nsnt + 1
94 ENDIF
95 ENDDO
96 ! ---------------------------
97
98 ! ---------------------------
99 ! loop over the M nodes
100 DO i = 1,nmn
101 m_node_id = msr(i)
102 iwcont(2,m_node_id) = iwcont(2,m_node_id)+1
103 nmnt = nmnt + 1
104 ENDDO
105 ! ---------------------------
106
107 RETURN
subroutine i24fic_getn(ns, irtse, is2se, ie, ns1, ns2)
Definition i24surfi.F:1921