OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
update_weight_inter_type2.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| update_weight_inter_type2 ../starter/source/spmd/domain_decomposition/update_weight_inter_type2.F
25!||--- called by ------------------------------------------------------
26!|| inint3 ../starter/source/interfaces/inter3d1/inint3.F
27!||--- uses -----------------------------------------------------
28!|| inter_cand_mod ../starter/share/modules1/inter_cand_mod.F
29!||====================================================================
30 SUBROUTINE update_weight_inter_type2(NELEMINT,INTERFACE_ID,NSN,NRTM,IFIEND,
31 1 N2D,IRECT,NSV,IRTL,INTER_CAND)
32!$COMMENT
33! UPDATE_WEIGHT_INTER_TYPE2 description :
34! save the contact data for interface type 2
35!
36! UPDATE_WEIGHT_INTER_TYPE2 organization :
37! for each contact, save :
38! * 2 main node IDs
39! * 1 secondary node ID
40! * 1 segment ID
41! * type of interface
42!$ENDCOMMENT
43
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER, INTENT(inout) :: NELEMINT
56 INTEGER, INTENT(in) :: INTERFACE_ID !< interface id
57 INTEGER, INTENT(in) :: NSN !< number of S node
58 INTEGER, INTENT(in) :: NRTM !< number of segment
59 INTEGER, INTENT(inout) :: IFIEND !< ???
60 INTEGER, INTENT(in) :: N2D !< flag for 2D/3D, 0-->3D, 1-->2D
61 INTEGER, DIMENSION(NSN), INTENT(in) :: IRTL
62 INTEGER, DIMENSION(4,NRTM), INTENT(in) :: IRECT !< list of M nodes for the NRTM segments
63 INTEGER, DIMENSION(NSN), INTENT(in) :: NSV !< list of S nodes
64 TYPE(inter_cand_), INTENT(inout) :: INTER_CAND
65C-----------------------------------------------
66C L o c a l V a r i a b l e s
67C-----------------------------------------------
68 INTEGER N,NIR,NN
69 INTEGER :: S_NODE_ID
70 INTEGER :: SEGMENT_ID
71C-----------------------------------------------
72 ! flush %ixint array to 0
73 inter_cand%IXINT(1:inter_cand%S_IXINT_1,nelemint+1:nelemint+nsn) = 0
74 inter_cand%ADDRESS(interface_id) = nelemint+1 ! save the adress of the first pair
75 nir=2
76 IF(n2d==0)nir=4
77 nn = 0
78 ! ---------------------------
79 ! loop over the secondary node
80 DO n = 1, nsn
81 s_node_id = nsv(n) ! S node id
82 segment_id = irtl(n) ! segment id
83 IF(segment_id/=0)THEN
84 nn = nn + 1
85 inter_cand%IXINT(1,nelemint+nn)=irect(1,segment_id)
86 inter_cand%IXINT(2,nelemint+nn)=irect(2,segment_id)
87 IF (nir==2) THEN
88 inter_cand%IXINT(3,nelemint+nn)=irect(1,segment_id)
89 inter_cand%IXINT(4,nelemint+nn)=irect(2,segment_id)
90 ELSE
91 inter_cand%IXINT(3,nelemint+nn)=irect(3,segment_id)
92 inter_cand%IXINT(4,nelemint+nn)=irect(4,segment_id)
93 END IF
94 inter_cand%IXINT(5,nelemint+nn)=s_node_id
95 inter_cand%IXINT(6,nelemint+nn)=2
96 inter_cand%IXINT(7,nelemint+nn)=segment_id
97 inter_cand%IXINT(8,nelemint+nn)=interface_id
98 END IF
99 ENDDO
100 ! ---------------------------
101 nelemint = nelemint+nn
102 ifiend = ifiend + nn
103 inter_cand%ADDRESS(interface_id+1) = nelemint ! save the adress of the last pair
104 ! ---------------------------
105 RETURN
106 END SUBROUTINE update_weight_inter_type2
107
subroutine update_weight_inter_type2(nelemint, interface_id, nsn, nrtm, ifiend, n2d, irect, nsv, irtl, inter_cand)