OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
w_ing2loc.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/.
23C
24!||====================================================================
25!|| w_ing2loc ../starter/source/restart/ddsplit/w_ing2loc.F
26!||--- called by ------------------------------------------------------
27!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
28!||--- calls -----------------------------------------------------
29!||--- uses -----------------------------------------------------
30!||====================================================================
31 SUBROUTINE w_ing2loc(
32 . ALE_CONNECTIVITY,ELEMID_L,NUMNOD,NODGLOB,NODLOCAL,NUMNOD_L,LEN_IA,NWALE)
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C D u m m y A r g u m e n t s
40C-----------------------------------------------
41 INTEGER NUMNOD, NUMNOD_L,LEN_IA,
42 . nodglob(*), nodlocal(*), elemid_l(*), nwale
43 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECTIVITY
44C-----------------------------------------------
45C L o c a l V a r i a b l e s
46C-----------------------------------------------
47 INTEGER I, J, NI, LEN, IAD1, IAD2
48 INTEGER, DIMENSION(:), ALLOCATABLE :: NB_CONNECT, CONNECTED, IAD_CONNECT, ADSKY
49
50 ALLOCATE(iad_connect(numnod_l + 1), nb_connect(numnod_l), adsky(numnod_l))
51 IF (ale_connectivity%has_nn_connect) THEN
52 DO i = 1, numnod_l
53 iad1 = ale_connectivity%NN_CONNECT%IAD_CONNECT(nodglob(i))
54 iad2 = ale_connectivity%NN_CONNECT%IAD_CONNECT(nodglob(i) + 1) - 1
55 nb_connect(i) = 0
56 DO j = iad1, iad2
57 IF (nodlocal(ale_connectivity%NN_CONNECT%CONNECTED(j)) > 0) THEN
58 nb_connect(i) = nb_connect(i) + 1
59 ENDIF
60 ENDDO
61 ENDDO
62
63 iad_connect(1) = 1
64 DO i = 2, numnod_l + 1
65 iad_connect(i) = iad_connect(i - 1) + nb_connect(i - 1)
66 ENDDO
67
68 len = iad_connect(numnod_l + 1)
69 ALLOCATE(connected(len))
70 connected(1:len) = 0
71 DO i = 1, numnod_l
72 adsky(i) = iad_connect(i)
73 ENDDO
74
75
76 DO i = 1, numnod_l
77 iad1 = ale_connectivity%NN_CONNECT%IAD_CONNECT(nodglob(i))
78 iad2 = ale_connectivity%NN_CONNECT%IAD_CONNECT(nodglob(i) + 1) - 1
79 DO j = iad1, iad2
80 IF (nodlocal(ale_connectivity%NN_CONNECT%CONNECTED(j)) > 0) THEN
81 connected(adsky(i)) = nodlocal(ale_connectivity%NN_CONNECT%CONNECTED(j))
82 adsky(i) = adsky(i) + 1
83 ENDIF
84 ENDDO
85 ENDDO
86
87 CALL write_i_c(iad_connect, numnod_l + 1)
88 CALL write_i_c(connected, len)
89
90 len_ia = len_ia + numnod_l + 1 + len
91 ENDIF
92
93 IF (ale_connectivity%has_ne_connect) THEN
94C Node - element connectivity
95 IF (ALLOCATED(connected)) DEALLOCATE(connected)
96 DO i = 1, numnod_l
97 iad1 = ale_connectivity%NE_CONNECT%IAD_CONNECT(nodglob(i))
98 iad2 = ale_connectivity%NE_CONNECT%IAD_CONNECT(nodglob(i) + 1) - 1
99 nb_connect(i) = 0
100 DO j = iad1, iad2
101 IF (elemid_l(ale_connectivity%NE_CONNECT%CONNECTED(j)) > 0) THEN
102 nb_connect(i) = nb_connect(i) + 1
103 ENDIF
104 ENDDO
105 ENDDO
106
107 iad_connect(1) = 1
108 DO i = 2, numnod_l + 1
109 iad_connect(i) = iad_connect(i - 1) + nb_connect(i - 1)
110 ENDDO
111
112 len = iad_connect(numnod_l + 1)
113 ALLOCATE(connected(len))
114
115 DO i = 1, numnod_l
116 adsky(i) = iad_connect(i)
117 ENDDO
118
119
120 DO i = 1, numnod_l
121 iad1 = ale_connectivity%NE_CONNECT%IAD_CONNECT(nodglob(i))
122 iad2 = ale_connectivity%NE_CONNECT%IAD_CONNECT(nodglob(i) + 1) - 1
123 DO j = iad1, iad2
124 IF (elemid_l(ale_connectivity%NE_CONNECT%CONNECTED(j)) > 0) THEN
125 connected(adsky(i)) = elemid_l(ale_connectivity%NE_CONNECT%CONNECTED(j))
126 adsky(i) = adsky(i) + 1
127 ENDIF
128 ENDDO
129 ENDDO
130
131 CALL write_i_c(iad_connect, numnod_l + 1)
132 CALL write_i_c(connected, len)
133
134 len_ia = len_ia + numnod_l + 1 + len
135 ENDIF
136
137 IF (ALLOCATED(iad_connect)) DEALLOCATE(iad_connect)
138 IF (ALLOCATED(connected)) DEALLOCATE(connected)
139 IF (ALLOCATED(adsky)) DEALLOCATE(adsky)
140 IF (ALLOCATED(nb_connect)) DEALLOCATE(nb_connect)
141
142 RETURN
143 END
subroutine w_ing2loc(ale_connectivity, elemid_l, numnod, nodglob, nodlocal, numnod_l, len_ia, nwale)
Definition w_ing2loc.F:33
void write_i_c(int *w, int *len)