OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
initnoise.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!|| initnoise ../engine/source/general_controls/computation/initnoise.F
25!||--- called by ------------------------------------------------------
26!|| noise ../engine/source/general_controls/computation/noise.F
27!||====================================================================
28 SUBROUTINE initnoise(IN,NOIADD,IXS,IWA,LENGTH,IXQ)
29C
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 "scrnoi_c.inc"
38#include "com01_c.inc"
39#include "com04_c.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER IN(*),IXS(NIXS,*),IWA(0:*),IXQ(NIXQ,*)
44 INTEGER NOIADD(*)
45C-----------------------------------------------
46C L o c a l V a r i a b l e s
47C-----------------------------------------------
48 INTEGER I,J,LENGTH,K
49C-----------------------------------------------
50C
51C ADRESSE DES NOEUDS SAUVES DS NOISE
52C
53 DO i=0,numnod
54 iwa(i)=0
55 ENDDO
56 DO i=1,nnoise
57 iwa(in(i))=i ! IN(I)=0 si noeud non present en SPMD
58 noiadd(i)=0
59 ENDDO
60 noiadd(nnoise+1)=0
61C
62C STOCKE DANS NOIADD(K) LE NOMBRE d'ELEMENTS CONNECTES AU NOEUD K-1
63C
64 IF(n2d==0)THEN
65 DO i=1,numels
66 DO j=2,9
67 k=iwa(ixs(j,i))
68 IF(k/=0)
69 . noiadd(k+1)=noiadd(k+1)+1
70 ENDDO
71 ENDDO
72 ELSE
73 DO i=1,numelq
74 DO j=2,5
75 k=iwa(ixq(j,i))
76 IF(k/=0)
77 . noiadd(k+1)=noiadd(k+1)+1
78 ENDDO
79 ENDDO
80 ENDIF
81C
82C ADRESSE PAR NOEUD DANS LE TABLEAU DES ELEMENTS A SAUVER DANS NOEUDS
83C
84 noiadd(1)=1
85 DO i=2,nnoise+1
86 noiadd(i)=noiadd(i)+noiadd(i-1)
87 ENDDO
88 length=noiadd(nnoise+1)-1
89c-----------
90 RETURN
91 END
92
93!||====================================================================
94!|| initnoise2 ../engine/source/general_controls/computation/initnoise.f
95!||--- called by ------------------------------------------------------
96!|| noise ../engine/source/general_controls/computation/noise.F
97!||====================================================================
98 SUBROUTINE initnoise2(IN,ELNOI,ELG,NOIADD,IXS,IWA,IPARG,IXQ)
99C
100C-----------------------------------------------
101C I m p l i c i t T y p e s
102C-----------------------------------------------
103#include "implicit_f.inc"
104C-----------------------------------------------
105C C o m m o n B l o c k s
106C-----------------------------------------------
107#include "scrnoi_c.inc"
108#include "com01_c.inc"
109#include "param_c.inc"
110C-----------------------------------------------
111C D u m m y A r g u m e n t s
112C-----------------------------------------------
113 INTEGER IN(*),IXS(NIXS,*),IXQ(NIXQ,*),IWA(*),IPARG(NPARG,*),
114 . ELNOI(*),ELG(*),NOIADD(*)
115C-----------------------------------------------
116C L o c a l V a r i a b l e s
117C-----------------------------------------------
118 INTEGER , DIMENSION (:), ALLOCATABLE :: KN
119 INTEGER I,J,LENGTH,K,II
120 INTEGER NG,NEL,ITY,NB2,NFT
121C-----------------------------------------------
122 IF(nnoise>0)THEN
123 ALLOCATE(kn(nnoise))
124 ENDIF
125 DO i=1,nnoise
126 kn(i)=0
127 ENDDO
128C
129C REMPLISSAGE DE ELNOI PAR LES ADRESSES DANS ELBUF
130C
131 DO ng=1,ngroup
132 ity =iparg(5,ng)
133 IF(ity==1)THEN
134 nel =iparg(2,ng)
135 nb2 =iparg(4,ng) + nel
136 nft =iparg(3,ng)
137 DO i=1,nel
138 ii=i+nft
139 DO j=2,9
140 k=iwa(ixs(j,ii))
141 IF(k /=0)THEN
142 elnoi(noiadd(k)+kn(k))=i
143 elg(noiadd(k)+kn(k))=ng
144 kn(k)=kn(k)+1
145 ENDIF
146 ENDDO
147 ENDDO
148 ELSEIF(ity==2)THEN
149 nel =iparg(2,ng)
150 nb2 =iparg(4,ng) + nel
151 nft =iparg(3,ng)
152 DO i=1,nel
153 ii=i+nft
154 DO j=2,5
155 k=iwa(ixq(j,ii))
156 IF(k /=0)THEN
157 elnoi(noiadd(k)+kn(k))=(i-1)*6
158 elg(noiadd(k)+kn(k))=ng
159 kn(k)=kn(k)+1
160 ENDIF
161 ENDDO
162 ENDDO
163 ENDIF
164
165 ENDDO
166C
167 IF(nnoise>0)THEN
168 DEALLOCATE(kn)
169 ENDIF
170C-----------
171 RETURN
172 END
173
174
175
176
177
178
179
subroutine initnoise2(in, elnoi, elg, noiadd, ixs, iwa, iparg, ixq)
Definition initnoise.F:99
subroutine initnoise(in, noiadd, ixs, iwa, length, ixq)
Definition initnoise.F:29