OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
compress_nnz.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!|| compress_c_nnz ../common_source/comm/compress_nnz.F
25!||--- calls -----------------------------------------------------
26!|| write_i_c ../common_source/tools/input_output/write_routtines.c
27!||====================================================================
28 SUBROUTINE compress_c_nnz(ARRAY,LEN)
29 IMPLICIT NONE
30C---------------------------------------------
31C Arguments
32C---------------------------------------------
33 INTEGER, INTENT(IN) :: LEN
34 INTEGER, INTENT(IN) :: ARRAY(LEN)
35C INTEGER, INTENT(INOUT) :: COMPR(*)
36C---------------------------------------------
37C Local Variables
38C---------------------------------------------
39 INTEGER I,J,IBEGIN, NNZ
40 LOGICAL continue_loop
41
42
43 ibegin = 1
44 j = 1
45 DO WHILE (ibegin <= len)
46 i = ibegin
47 nnz = 0
48 continue_loop = (array(i) /= ichar(' '))
49 DO WHILE(continue_loop)
50 IF(i <= len) THEN
51 IF(array(i) /= ichar(' ')) THEN
52 continue_loop = .true.
53 nnz = nnz + 1
54 i = i + 1
55 ELSE
56 continue_loop = .false.
57 ENDIF
58 ELSE
59 continue_loop = .false.
60 ENDIF
61 ENDDO
62 IF(nnz > 0) THEN
63C COMPR(J) = IBEGIN
64C COMPR(J+1) = NNZ
65 CALL write_i_c(ibegin,1)
66 CALL write_i_c(nnz,1)
67 j = j + 2
68 CALL write_i_c(array(ibegin:ibegin+nnz-1),nnz)
69 j = j + nnz
70 ENDIF
71 ibegin = i + 1
72 ENDDO
73C COMPR(J) = -1
74 i = -1
75 CALL write_i_c(i,1)
76C WRITE(6,*) LEN,"compressed into ",J, dble(J)/dble(LEN)
77 END SUBROUTINE
78
79
80!||====================================================================
81!|| compress_i_nnz ../common_source/comm/compress_nnz.F
82!||--- called by ------------------------------------------------------
83!|| copy_ival_dummy ../starter/source/restart/ddsplit/inter_tools.F
84!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
85!|| write_intbuf ../engine/source/output/restart/write_intbuf.F
86!|| wrrestp ../engine/source/output/restart/wrrestp.F
87!||--- calls -----------------------------------------------------
88!|| write_i_c ../common_source/tools/input_output/write_routtines.c
89!||====================================================================
90 SUBROUTINE compress_i_nnz(ARRAY,LEN)
91 IMPLICIT NONE
92C---------------------------------------------
93C Arguments
94C---------------------------------------------
95 INTEGER, INTENT(IN) :: LEN
96 INTEGER, INTENT(IN) :: ARRAY(LEN)
97C INTEGER, INTENT(INOUT) :: COMPR(*)
98C---------------------------------------------
99C Local Variables
100C---------------------------------------------
101 INTEGER I,J,IBEGIN, NNZ
102 LOGICAL continue_loop
103
104 ibegin = 1
105 j = 1
106 DO WHILE (ibegin <= len)
107 i = ibegin
108 nnz = 0
109 continue_loop = (array(i) /= 0)
110 DO WHILE(continue_loop)
111 IF(i <= len) THEN
112 IF(array(i) /= 0) THEN
113 continue_loop = .true.
114 nnz = nnz + 1
115 i = i + 1
116 ELSE
117 continue_loop = .false.
118 ENDIF
119 ELSE
120 continue_loop = .false.
121 ENDIF
122 ENDDO
123 IF(nnz > 0) THEN
124C COMPR(J) = IBEGIN
125C COMPR(J+1) = NNZ
126 CALL write_i_c(ibegin,1)
127 CALL write_i_c(nnz,1)
128 j = j + 2
129 CALL write_i_c(array(ibegin:ibegin+nnz-1),nnz)
130 j = j + nnz
131 ENDIF
132 ibegin = i + 1
133 ENDDO
134C COMPR(J) = -1
135 i = -1
136 CALL write_i_c(i,1)
137C WRITE(6,*) LEN,"I compressed into ",J, dble(J)/dble(LEN)
138 END SUBROUTINE
139
140!||====================================================================
141!|| compress_r_nnz ../common_source/comm/compress_nnz.F
142!||--- called by ------------------------------------------------------
143!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
144!|| split_cand_rval_dummy ../starter/source/restart/ddsplit/inter_tools.F
145!|| split_node_rval_dummy ../starter/source/restart/ddsplit/inter_tools.F
146!|| w_geo ../starter/source/restart/ddsplit/w_geo.F
147!|| write_intbuf ../engine/source/output/restart/write_intbuf.F
148!|| wrrestp ../engine/source/output/restart/wrrestp.F
149!||--- calls -----------------------------------------------------
150!|| write_db ../common_source/tools/input_output/write_db.F
151!|| write_i_c ../common_source/tools/input_output/write_routtines.c
152!||====================================================================
153 SUBROUTINE compress_r_nnz(ARRAY,LEN)
154#include "implicit_f.inc"
155C---------------------------------------------
156C Arguments
157C---------------------------------------------
158 INTEGER, INTENT(IN) :: LEN
159 my_real , INTENT(IN) :: array(len)
160C INTEGER, INTENT(INOUT) :: COMPR(*)
161C---------------------------------------------
162C Local Variables
163C---------------------------------------------
164 INTEGER I,J,IBEGIN, NNZ
165 LOGICAL continue_loop
166
167 ibegin = 1
168 j = 1
169 DO WHILE (ibegin <= len)
170 i = ibegin
171 nnz = 0
172 continue_loop = (array(i) /= 0)
173 DO WHILE(continue_loop)
174 IF(i <= len) THEN
175 IF(array(i) /= 0) THEN
176 continue_loop = .true.
177 nnz = nnz + 1
178 i = i + 1
179 ELSE
180 continue_loop = .false.
181 ENDIF
182 ELSE
183 continue_loop = .false.
184 ENDIF
185 ENDDO
186 IF(nnz > 0) THEN
187C COMPR(J) = IBEGIN
188C COMPR(J+1) = NNZ
189 CALL write_i_c(ibegin,1)
190 CALL write_i_c(nnz,1)
191 j = j + 2
192 CALL write_db(array(ibegin:ibegin+nnz-1),nnz)
193 j = j + nnz
194 ENDIF
195 ibegin = i + 1
196 ENDDO
197C COMPR(J) = -1
198 i = -1
199 CALL write_i_c(i,1)
200C WRITE(6,*) LEN,"R compressed into ",J, dble(J)/dble(LEN)
201 END SUBROUTINE
subroutine compress_i_nnz(array, len)
subroutine compress_c_nnz(array, len)
subroutine compress_r_nnz(array, len)
#define my_real
Definition cppsort.cpp:32
subroutine write_db(a, n)
Definition write_db.F:140
void write_i_c(int *w, int *len)