OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i2sms26.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!|| i2sms26 ../engine/source/interfaces/interf/i2sms26.F
25!||--- called by ------------------------------------------------------
26!|| i2for26 ../engine/source/interfaces/interf/i2for26.F
27!|| i2for26p ../engine/source/interfaces/interf/i2for26p.F
28!||--- uses -----------------------------------------------------
29!|| message_mod ../engine/share/message_module/message_mod.F
30!||====================================================================
31 SUBROUTINE i2sms26(JLT ,IX1 ,IX2 ,IX3 ,IX4 ,
32 . NSVG ,STIF ,NOINT ,
33 . DMINT2,NODNX_SMS ,VIS ,DTI)
34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE message_mod
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42#include "comlock.inc"
43C-----------------------------------------------
44C G l o b a l P a r a m e t e r s
45C-----------------------------------------------
46#include "mvsiz_p.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "sms_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER JLT, NOINT,
55 . IX1(MVSIZ),IX2(MVSIZ),IX3(MVSIZ),IX4(MVSIZ),NSVG(MVSIZ),
56 . nodnx_sms(*)
58 . stif(4,mvsiz), vis(4,mvsiz), dmint2(4,*), dti
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I, IG, NN, NISKYL1, NISKYL
63 my_real
64 . dts, fac
65C=======================================================================
66 DO i=1,jlt
67 dmint2(1,i)=zero
68 dmint2(2,i)=zero
69 dmint2(3,i)=zero
70 dmint2(4,i)=zero
71C
72 IF (nsvg(i) < 0) cycle
73 IF ((idtmins_int == 0 .AND. nodnx_sms(nsvg(i))+
74 . nodnx_sms(ix1(i))+
75 . nodnx_sms(ix2(i))+
76 . nodnx_sms(ix3(i))+
77 . nodnx_sms(ix4(i))==0) .OR.
78 . stif(1,i)+stif(2,i)+stif(3,i)+stif(4,i)==zero) THEN
79 cycle
80 END IF
81C
82 IF (idtmins_int == 0 .AND. nodnx_sms(nsvg(i))+
83 . nodnx_sms(ix1(i))+
84 . nodnx_sms(ix2(i))+
85 . nodnx_sms(ix3(i))+
86 . nodnx_sms(ix4(i))/=0) THEN
87 dts = dtmins/dtfacs
88 dti = min(dti,dtmins)
89 ELSE
90 dts = dtmins_int/dtfacs_int
91 dti = min(dti,dtmins_int)
92 END IF
93
94C
95 dmint2(1,i) = half * dts * ( dts * stif(1,i) + vis(1,i) )
96 dmint2(2,i) = half * dts * ( dts * stif(2,i) + vis(2,i) )
97 dmint2(3,i) = half * dts * ( dts * stif(3,i) + vis(3,i) )
98 IF (ix4(i) /= ix3(i)) THEN
99 dmint2(4,i) = half * dts * ( dts * stif(4,i) + vis(4,i) )
100 ENDIF
101 ENDDO
102C-----------
103 RETURN
104 END
105C
#define my_real
Definition cppsort.cpp:32
subroutine i2sms26(jlt, ix1, ix2, ix3, ix4, nsvg, stif, noint, dmint2, nodnx_sms, vis, dti)
Definition i2sms26.F:34
#define min(a, b)
Definition macros.h:20