OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
preplyxfem.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!|| preplyxfem ../starter/source/properties/composite_options/stack/preplyxfem.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||====================================================================
28 SUBROUTINE preplyxfem(
29 1 MS_PLY0,ZI_PLY0,IEL, INOD , IXC ,MS_PLY,ZI_PLY,ADDCNE ,
30 2 MSZ20,MSZ2)
31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C C o m m o n B l o c k s
37C-----------------------------------------------
38#include "com04_c.inc"
39#include "param_c.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER IXC(NIXC,*), ADDCNE(0:*),IEL(*),INOD(*)
44 my_real
45 . ms_ply0(numnod,*), zi_ply0(numnod,*),
46 . ms_ply(nplyxfe,*), zi_ply(nplyxfe,*),
47 . msz20(*),msz2(*)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER I,II,K,N1,J,N
52 my_real
53 . msz
54C-----------------------------------------------
55C S o u r c e L i n e s
56C-----------------------------------------------
57 addcne(0)=0
58 addcne(1)= 0
59 DO i=1,numnod
60 ii = inod(i)
61 addcne(i + 1) = 0
62 msz = zero
63 IF( ii > 0 )THEN
64 msz2(ii) = zero
65 DO j=1,nplymax
66 ms_ply(ii,j) = ms_ply0(i,j)
67 zi_ply(ii,j) = zi_ply0(i,j)
68C ementary compute
69cc MSZ2(II) = MSZ20(I)
70c nodale compute
71 msz2(ii) = msz2(ii) +
72 . ms_ply(ii,j)*zi_ply(ii,j)*zi_ply(ii,j)
73 ENDDO
74 IF(msz2(ii) == zero) msz2(ii) = ep30
75 ENDIF
76 ENDDO
77C
78 DO i=1,numelc
79 IF(iel(i) > 0 ) THEN
80 DO k=2,5
81 n = inod(ixc(k,i)) + 1
82 addcne(n) = addcne(n) + 1
83 ENDDO
84 ENDIF
85 ENDDO
86 addcne(1) = 1
87 DO i=2,nplyxfe + 1
88 addcne(i) = addcne(i) + addcne(i-1)
89 END DO
90C
91 RETURN
92 END
93!||====================================================================
94!|| fillcne_pxfem ../starter/source/properties/composite_options/stack/preplyxfem.F
95!||--- called by ------------------------------------------------------
96!|| lectur ../starter/source/starter/lectur.F
97!||--- calls -----------------------------------------------------
98!||====================================================================
99 SUBROUTINE fillcne_pxfem(
100 1 IEL , INOD, IXC,CEP, ADDCNE, CNE,CEL )
101C-----------------------------------------------
102C I m p l i c i t T y p e s
103C-----------------------------------------------
104#include "implicit_f.inc"
105C-----------------------------------------------
106C C o m m o n B l o c k s
107C-----------------------------------------------
108#include "com01_c.inc"
109#include "com04_c.inc"
110#include "param_c.inc"
111C-----------------------------------------------
112C D u m m y A r g u m e n t s
113C-----------------------------------------------
114 INTEGER IXC(NIXC,*),ADDCNE(0:*), CNE(*),IEL(*),INOD(*),
115 . CEP(*),CEL(*)
116C-----------------------------------------------
117C L o c a l V a r i a b l e s
118C-----------------------------------------------
119 INTEGER I, J, K, N, ADSKY(0:NPLYXFE+1),N1,PROC,NG,
120 . INDX, INDEX(NUMELC),P,II,NIN,INDEXC(2*NUMELC),
121 . WORK(70000),ITRI(NUMELC)
122C-----------------------------------------------
123C S o u r c e L i n e s
124C-----------------------------------------------
125C CALCUL DE CNE ADDCNE
126C-----------------------------------------------
127 DO i = 0, nplyxfe + 1
128 adsky(i) = addcne(i)
129 ENDDO
130C
131C
132C tri des elements locaux suivants num user
133C
134 DO i = 1, numelc
135 itri(i) = ixc(7,i)
136 ENDDO
137 CALL my_orders(0,work,itri,indexc,numelc,1)
138
139 indx = 0
140 DO j=1,numelc
141 i = indexc(j)
142!! DO I = 1,NUMELC
143 IF(iel(i) > 0 )THEN
144 indx = indx + 1
145 DO k=1,4
146 n = ixc(k+1,i)
147 n1 = inod(n)
148 cne(adsky(n1)) = i
149 adsky(n1) = adsky(n1) + 1
150 ENDDO
151 index(indx) = i
152 ENDIF
153 ENDDO
154C
155 DO proc = 1, nspmd
156 nin = 0
157!! DO I=1,INDX
158 DO ii=1,numelc
159!! II = INDEX(I)
160 ng = ii + numels + numelq
161 p = cep(ng) + 1
162 IF (p == proc) THEN
163 j = iel(ii)
164 IF(j > 0) THEN
165 nin = nin + 1
166 cel(j) = nin
167 ENDIF
168 ENDIF
169 ENDDO
170 ENDDO
171C
172 RETURN
173 END
void my_orders(int *mode, int *iwork, int *data, int *index, int *n, int *irecl)
Definition my_orders.c:82
subroutine fillcne_pxfem(iel, inod, ixc, cep, addcne, cne, cel)
Definition preplyxfem.F:101
subroutine preplyxfem(ms_ply0, zi_ply0, iel, inod, ixc, ms_ply, zi_ply, addcne, msz20, msz2)
Definition preplyxfem.F:31