OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
thtrus_count.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!|| thtrus_count ../engine/source/output/th/thtrus_count.F
25!||--- called by ------------------------------------------------------
26!|| init_th ../engine/source/output/th/init_th.F
27!||====================================================================
28 SUBROUTINE thtrus_count(NTHGRP2, ITHGRP ,WA_SIZE, INDEX_WA_TRUS ,
29 . IPARG ,ITHBUF,SITHBUF )
30C-----------------------------------------------
31C I m p l i c i t T y p e s
32C-----------------------------------------------
33#include "implicit_f.inc"
34C-----------------------------------------------
35C C o m m o n B l o c k s
36C-----------------------------------------------
37#include "com01_c.inc"
38#include "scr05_c.inc"
39#include "task_c.inc"
40#include "param_c.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER,INTENT(IN) :: SITHBUF
45 INTEGER IPARG(NPARG,*),ITHBUF(*)
46 INTEGER, INTENT(inout) :: WA_SIZE,NTHGRP2
47 INTEGER, DIMENSION(2*NTHGRP2+1), INTENT(inout) :: INDEX_WA_TRUS
48 INTEGER, DIMENSION(NITHGR,*), INTENT(in) :: ITHGRP
49C-----------------------------------------------
50C L o c a l V a r i a b l e s
51C-----------------------------------------------
52 LOGICAL :: BOOL
53 INTEGER II,I,N,IH,NG,ITY,MTE,K,L,LWA,NEL,NFT,J
54 INTEGER :: J_FIRST,NITER,IAD,NN,IADV,NVAR,ITYP,IJK
55 INTEGER, DIMENSION(NTHGRP2) :: INDEX_TRUS
56C-----------------------------------------------
57C-------------------------
58C ELEMENTS BARRES
59C-------------------------
60 ijk = 0
61 wa_size = 0
62 index_trus(1:nthgrp2) = 0
63 DO niter=1,nthgrp2
64 ityp=ithgrp(2,niter)
65 nn =ithgrp(4,niter)
66 iad =ithgrp(5,niter)
67 nvar=ithgrp(6,niter)
68 iadv=ithgrp(7,niter)
69 ii=0
70 IF(ityp==4)THEN
71
72 ii=0
73 ih=iad
74 DO WHILE (ithbuf(ih+nn) /= ispmd .AND. ih < iad+nn)
75 ih = ih + 1
76 ENDDO
77 IF (ih >= iad+nn) GOTO 666
78C
79 DO ng=1,ngroup
80 ity=iparg(5,ng)
81 IF (ity == 4) THEN
82 mte=iparg(1,ng)
83 nel=iparg(2,ng)
84 nft=iparg(3,ng)
85 DO i=1,nel
86 n=i+nft
87 k=ithbuf(ih)
88 IF (k == n) THEN
89 ih=ih+1
90 ii = ((ih-1) - iad)*nvar
91 DO WHILE (ithbuf(ih+nn) /= ispmd .AND. ih < iad+nn)
92 ih = ih + 1
93 ENDDO
94 IF (ih > iad+nn) GOTO 666
95 wa_size = wa_size + nvar + 1
96 ENDIF ! IF (K == N)
97 ENDDO ! DO I=1,NEL
98 ENDIF ! IF (ITY == 4)
99 ENDDO ! DO NG=1,NGROUP
100 ENDIF
101 666 continue
102 index_trus(niter) = wa_size
103 ENDDO
104
105
106 j_first = 0
107 bool = .true.
108 DO i=1,nthgrp2
109 IF(bool.EQV..true.) THEN
110 IF( index_trus(i)/=0 ) THEN
111 bool = .false.
112 j_first = i
113 ENDIF
114 ENDIF
115 ENDDO
116
117 j = 0
118 IF(j_first>0) THEN
119 j=j+1
120 index_wa_trus(j) = index_trus(j_first)
121 j=j+1
122 index_wa_trus(j) = j_first
123 DO i=j_first+1,nthgrp2
124 IF( index_trus(i)-index_trus(i-1)>0 ) THEN
125 j=j+1
126 index_wa_trus(j) = index_trus(i)
127 j=j+1
128 index_wa_trus(j) = i
129 ENDIF
130 ENDDO
131 ENDIF
132 index_wa_trus(2*nthgrp2+1) = j ! number of non-zero index
133C-----------
134 RETURN
135 END SUBROUTINE thtrus_count
subroutine thtrus_count(nthgrp2, ithgrp, wa_size, index_wa_trus, iparg, ithbuf, sithbuf)