OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
inintmass.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!|| inintmass ../starter/source/interfaces/inter3d1/inintmass.F
25!||--- called by ------------------------------------------------------
26!|| initia ../starter/source/elements/initia/initia.F
27!||--- uses -----------------------------------------------------
28!|| message_mod ../starter/share/message_module/message_mod.f
29!||====================================================================
30 SUBROUTINE inintmass( IPARI, INTBUF_TAB, MS ,ISTIF_DT)
31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34 USE message_mod
35 USE intbufdef_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com04_c.inc"
44#include "param_c.inc"
45C-----------------------------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER , INTENT(INOUT) :: ISTIF_DT
49 INTEGER , INTENT(IN ) :: IPARI(NPARI,NINTER)
50 my_real , INTENT(IN ) :: ms(numnod)
51 TYPE(intbuf_struct_) , INTENT(INOUT) :: INTBUF_TAB(NINTER)
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER
56 . N ,NS ,N1, N2, N3 ,N4 ,I ,NI ,NTY ,NRTM ,NSN ,ISTIF_MSDT ,FLAGDT ,
57 . NEDGE
58 my_real
59 . stfacm ,ms1 ,ms2 ,ms3 ,ms4 ,dtstif
60C----------------------------------------------------------
61C Main and secondary masses needed for contact stiffness computation
62C----------------------------------------------------------
63 DO n=1,ninter
64 nty = ipari(7,n)
65 IF(nty==24.OR.nty==25) THEN
66 istif_msdt = ipari(97,n)
67 IF(istif_msdt > 0) THEN
68 nrtm = ipari(4,n)
69 nsn = ipari(5,n)
70 stfacm = intbuf_tab(n)%VARIABLES(47)
71 DO i=1,nsn
72 ns = intbuf_tab(n)%NSV(i)
73 intbuf_tab(n)%STIFMSDT_S(i) = stfacm*ms(ns)
74 ENDDO
75 DO i=1,nrtm
76 n1=intbuf_tab(n)%IRECTM(4*(i-1)+1)
77 ms1 = ms(n1)
78 n2=intbuf_tab(n)%IRECTM(4*(i-1)+2)
79 ms2 = ms(n2)
80 n3=intbuf_tab(n)%IRECTM(4*(i-1)+3)
81 ms3 = ms(n3)
82 n4=intbuf_tab(n)%IRECTM(4*(i-1)+4)
83 IF (n3 /= n4) THEN
84 ms4 = ms(n4)
85 intbuf_tab(n)%STIFMSDT_M(i) = stfacm*fourth*(ms1+ms2+ms3+ms4)
86 ELSE
87 intbuf_tab(n)%STIFMSDT_M(i) = stfacm*third*(ms1+ms2+ms3)
88 ENDIF
89 ENDDO
90
91 IF(nty==25.AND.ipari(58,n) > 0) THEN
92 nedge = ipari(68,n)
93 DO i=1,nedge
94 n1= intbuf_tab(n)%LEDGE(nledge*(i-1)+5)
95 n2= intbuf_tab(n)%LEDGE(nledge*(i-1)+6)
96 ms1 = ms(n1)
97 ms2 = ms(n2)
98 intbuf_tab(n)%STIFMSDT_EDG(i) = half*stfacm*(ms1+ms2)
99 ENDDO
100 ENDIF
101 ENDIF
102 ENDIF
103 ENDDO
104C---- ISTIF_DT flag to compute initial time step if no contact time step is set -----
105 flagdt = 0
106 DO n=1,ninter
107 nty = ipari(7,n)
108 IF(nty==24.OR.nty==25) THEN
109 istif_msdt = ipari(97,n)
110 dtstif = intbuf_tab(n)%VARIABLES(48)
111 IF(istif_msdt > 0) THEN
112 IF (dtstif == zero) flagdt = 1
113 ENDIF
114 ENDIF
115 ENDDO
116 istif_dt = flagdt
117
118 RETURN
119 END SUBROUTINE inintmass
#define my_real
Definition cppsort.cpp:32
subroutine inintmass(ipari, intbuf_tab, ms, istif_dt)
Definition inintmass.F:31
program starter
Definition starter.F:39