OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
count3.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!|| count3 ../starter/source/interfaces/interf1/count3.F
26!||--- called by ------------------------------------------------------
27!|| inslin ../starter/source/interfaces/interf1/inslin.F
28!|| insurf ../starter/source/interfaces/interf1/insurf.F
29!|| insurf23 ../starter/source/interfaces/interf1/insurf23.F
30!||--- calls -----------------------------------------------------
31!||====================================================================
32 SUBROUTINE count3(IRECT,MNN,N,NRT,NTAG)
33C-----------------------------------------------------------------------
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 N, NRT
42 INTEGER IRECT(*), MNN(*)
43 INTEGER, DIMENSION(0:2*NUMNOD), INTENT(INOUT) :: NTAG
44C-----------------------------------------------
45C C o m m o n B l o c k s
46C-----------------------------------------------
47#include "com04_c.inc"
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER IWORK(70000)
52 INTEGER I, NN, K,NINDEX0
53 INTEGER, DIMENSION(:), ALLOCATABLE :: INDEX0
54C-----------------------------------------------
55C
56 ALLOCATE(index0(2*numnod))
57 ntag(0) = 1 ! special case IRECT=0
58 n = 0
59 nindex0 = 0
60 DO i=1,nrt*4 ! 4 : size of IRECT
61 nn = irect(i)
62 IF(ntag(nn) == 0) THEN
63 n=n+1
64 mnn(n)=nn
65 ntag(nn)=1
66 nindex0 = nindex0 + 1
67 index0(nindex0) = nn
68 END IF
69 ENDDO
70C Need to sort MNM but avoid treatment over NUMNOD if too big
71 IF(n>numnod/10)THEN ! test to check which treatment is best
72 n=0
73 DO i=1,numnod
74 IF(ntag(i) /= 0) THEN
75 n=n+1
76 mnn(n)=i
77 ntag(i) = 0
78 END IF
79 END DO
80 ELSE ! N needs to be at least < NUMNOD/2
81 CALL my_orders(0,iwork,mnn,ntag(1),n,1)
82 DO i=1,n
83 ntag(n+i)=mnn(i)
84 END DO
85 DO i=1,n
86 mnn(i)=ntag(n+ntag(i))
87 END DO
88 DO i=1,n
89 ntag(n+ntag(i)) = 0
90 ENDDO
91 DO i=1,n
92 ntag(n+i) = 0
93 ntag(i) = 0
94 ENDDO
95 END IF
96
97#include "vectorize.inc"
98 DO k = 1,nindex0
99 ntag(index0(k)) = 0
100 ENDDO
101
102 DEALLOCATE(index0)
103C
104 RETURN
105 END
subroutine count3(irect, mnn, n, nrt, ntag)
Definition count3.F:33
void my_orders(int *mode, int *iwork, int *data, int *index, int *n, int *irecl)
Definition my_orders.c:82