OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
qmasi2b.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!|| qmasi2b ../starter/source/elements/solid_2d/quad/qmasi2b.F
25!||--- called by ------------------------------------------------------
26!|| binit2 ../starter/source/ale/bimat/binit2.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE qmasi2b(PM,MAT,MS,VOL,MSQ,WMA,IPART,PARTSAV,
30 . IX1, IX2, IX3, IX4 ,X ,V)
31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34 USE ale_mod
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C G l o b a l P a r a m e t e r s
41C-----------------------------------------------
42#include "mvsiz_p.inc"
43#include "com04_c.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 my_real pm(npropm,nummat), ms(*), vol(*),wma(*),partsav(20,*),msq(*),x(3,*),v(3,*)
48 INTEGER MAT(*),IPART(*), IX1(*), IX2(*), IX3(*), IX4(*)
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52#include "vect01_c.inc"
53#include "param_c.inc"
54C-----------------------------------------------
55C L o c a l V a r i a b l e s
56C-----------------------------------------------
57 INTEGER I,IP ,I1 ,I2 ,I3 ,I4
58 my_real yy ,zz ,yz , mass(mvsiz)
59C-----------------------------------------------
60C S o u r c e L i n e s
61C-----------------------------------------------
62 DO i=lft,llt
63 mass(i)=pm(89,mat(i))*vol(i)*fourth
64 ENDDO
65
66C calcul mass initiale en arithmetique // pour le spmd
67 DO i=lft,llt
68 msq(i)=msq(i)+mass(i)
69 ENDDO
70
71 IF(jale>0 .AND. ale%GRID%NWALE==4)THEN
72 DO i=lft,llt
73 wma(ix1(i))=wma(ix1(i))+one
74 wma(ix2(i))=wma(ix2(i))+one
75 wma(ix3(i))=wma(ix3(i))+one
76 wma(ix4(i))=wma(ix4(i))+one
77 ENDDO
78 ENDIF
79
80 DO i=lft,llt
81 ip = ipart(i)
82 partsav(1,ip)=partsav(1,ip) + four*mass(i)
83C
84 i1 = ix1(i)
85 i2 = ix2(i)
86 i3 = ix3(i)
87 i4 = ix4(i)
88 yy = (x(2,i1)*x(2,i1)+x(2,i2)*x(2,i2)+x(2,i3)*x(2,i3)+x(2,i4)*x(2,i4))
89 yz = (x(2,i1)*x(3,i1)+x(2,i2)*x(3,i2)+x(2,i3)*x(3,i3)+x(2,i4)*x(3,i4))
90 zz = (x(3,i1)*x(3,i1)+x(3,i2)*x(3,i2)+x(3,i3)*x(3,i3)+x(3,i4)*x(3,i4))
91c
92 partsav(5,ip) =partsav(5,ip) + mass(i) * (yy+zz)
93 partsav(6,ip) =partsav(6,ip) + mass(i) * zz
94 partsav(7,ip) =partsav(7,ip) + mass(i) * yy
95 partsav(9,ip) =partsav(9,ip) - mass(i) * yz
96C
97 partsav(12,ip)=partsav(12,ip) + mass(i)*(v(2,i1)+v(2,i2)+v(2,i3)+v(2,i4))
98 partsav(13,ip)=partsav(13,ip) + mass(i)*(v(3,i1)+v(3,i2)+v(3,i3)+v(3,i4))
99 partsav(14,ip)=partsav(14,ip) + half * mass(i) * (v(2,i1)*v(2,i1)+v(3,i1)*v(3,i1)
100 . +v(2,i2)*v(2,i2)+v(3,i2)*v(3,i2)
101 . +v(2,i3)*v(2,i3)+v(3,i3)*v(3,i3)
102 . +v(2,i4)*v(2,i4)+v(3,i4)*v(3,i4))
103C
104 ENDDO
105
106 RETURN
107 END
#define my_real
Definition cppsort.cpp:32
type(ale_) ale
Definition ale_mod.F:249
subroutine qmasi2b(pm, mat, ms, vol, msq, wma, ipart, partsav, ix1, ix2, ix3, ix4, x, v)
Definition qmasi2b.F:31