OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
rmas12.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!|| rmas12 ../starter/source/elements/spring/rmas12.f
26!||--- called by ------------------------------------------------------
27!|| rinit3 ../starter/source/elements/spring/rinit3.F
28!||====================================================================
29 SUBROUTINE rmas12(IXR,GEO,PARTSAV,X ,V ,IPART,XL ,MSR ,INR,MSRT)
30C----------------------------------------------
31C INITIALISATION DES MASSES NODALES
32C----------------------------------------------
33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C C o m m o n B l o c k s
39C-----------------------------------------------
40#include "com01_c.inc"
41#include "param_c.inc"
42#include "vect01_c.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER :: IXR(NIXR,*),IPART(*)
47 my_real :: geo(npropg,*),x(3,*),v(3,*),partsav(20,*), xl(*),msr(3,*),inr(3,*),msrt(*)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER I, IP,I1,I2,I3
52 my_real :: xx,yy,zz,xy,yz,zx
53 my_real :: ems, xi,ems2, xi2
54C---------------------------------------------------------------------
55 IF(irest_mselt/=0)THEN
56 DO i=lft,llt
57 msrt(i)=geo(1,ixr(1,i+nft))*xl(i)
58 ENDDO
59 END IF
60C----------------------------------------------
61C MASSE ELEMENT /2
62C----------------------------------------------
63C----------------------------------------------
64C INITIALISATION DES MASSES NODALES
65C----------------------------------------------
66
67 DO i=lft,llt
68 i1 = ixr(2,i+nft)
69 i2 = ixr(3,i+nft)
70 i3 = ixr(4,i+nft)
71C
72 ems = half * geo(1,ixr(1,i+nft))*xl(i)
73 ems2= half * ems
74
75 xi = half * geo(9,ixr(1,i+nft))
76 xi2 = half * xi*xl(i)
77 msr(1,i) = ems2
78 msr(2,i) = ems
79 msr(3,i) = ems2
80 inr(1,i) = xi2
81 inr(2,i) = xi
82 inr(3,i) = xi2
83C
84C
85 ip=ipart(i)
86 partsav(1,ip)=partsav(1,ip) + two*ems
87 partsav(2,ip)=partsav(2,ip)
88 . + ems2*(x(1,i1)+x(1,i3)) + ems*x(1,i2)
89 partsav(3,ip)=partsav(3,ip)
90 . + ems2*(x(2,i1)+x(2,i3)) + ems*x(2,i2)
91 partsav(4,ip)=partsav(4,ip)
92 . + ems2*(x(3,i1)+x(3,i3)) + ems*x(3,i2)
93 xx = half*(x(1,i1)*x(1,i1)+x(1,i3)*x(1,i3)) + x(1,i2)*x(1,i2)
94 xy = half*(x(1,i1)*x(2,i1)+x(2,i3)*x(2,i3)) + x(1,i2)*x(2,i2)
95 yy = half*(x(2,i1)*x(2,i1)+x(3,i3)*x(3,i3)) + x(2,i2)*x(2,i2)
96 yz = half*(x(2,i1)*x(3,i1)+x(1,i3)*x(1,i3)) + x(2,i2)*x(3,i2)
97 zz = half*(x(3,i1)*x(3,i1)+x(2,i3)*x(2,i3)) + x(3,i2)*x(3,i2)
98 zx = half*(x(3,i1)*x(1,i1)+x(3,i3)*x(3,i3)) + x(3,i2)*x(1,i2)
99 partsav(5,ip) =partsav(5,ip) + two*xi + ems * (yy+zz)
100 partsav(6,ip) =partsav(6,ip) + two*xi + ems * (zz+xx)
101 partsav(7,ip) =partsav(7,ip) + two*xi + ems * (xx+yy)
102 partsav(8,ip) =partsav(8,ip) - ems * xy
103 partsav(9,ip) =partsav(9,ip) - ems * yz
104 partsav(10,ip)=partsav(10,ip) - ems * zx
105C
106 partsav(11,ip)=partsav(11,ip)
107 . + ems2*(v(1,i1)+v(1,i3)) + ems*v(1,i2)
108 partsav(12,ip)=partsav(12,ip)
109 . + ems2*(v(2,i1)+v(2,i3)) + ems*v(2,i2)
110 partsav(13,ip)=partsav(13,ip)
111 . + ems2*(v(3,i1)+v(3,i3)) + ems*v(3,i2)
112 partsav(14,ip)=partsav(14,ip) + half * ems2 *
113 . (v(1,i1)*v(1,i1)+v(2,i1)*v(2,i1)+v(3,i1)*v(3,i1)
114 . +v(1,i3)*v(1,i3)+v(2,i3)*v(2,i3)+v(3,i3)*v(3,i3))
115 . + half * ems *
116 . (v(1,i2)*v(1,i2)+v(2,i2)*v(2,i2)+v(3,i2)*v(3,i2))
117 ENDDO
118C
119 RETURN
120 END
#define my_real
Definition cppsort.cpp:32
subroutine rmas12(ixr, geo, partsav, x, v, ipart, xl, msr, inr, msrt)
Definition rmas12.F:30
program starter
Definition starter.F:39