OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
joint_elem_timestep.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!|| joint_elem_timestep ../engine/source/elements/joint/joint_elem_timestep.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.F
27!||--- uses -----------------------------------------------------
28!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
29!||====================================================================
30 SUBROUTINE joint_elem_timestep(MS,IN,STIFN,STIFR,IXR,IPART,
31 1 IPARTR,IGEO,GEO,NPBY,IPARG,ELBUF_TAB,
32 2 DT2T,NELTST,ITYPTST,NRBODY,ITAB)
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE elbufdef_mod
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com01_c.inc"
45#include "param_c.inc"
46#include "scr02_c.inc"
47#include "scr17_c.inc"
48#include "scr18_c.inc"
49#include "sms_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER IXR(NIXR,*),IPART(LIPART1,*),IPARTR(*),
54 . IGEO(NPROPGI,*),NPBY(NNPBY,*),
55 . iparg(nparg,*),neltst,ityptst,nrbody,itab(*)
56 my_real stifn(*), stifr(*),ms(*) ,in(*),geo(npropg,*),dt2t
57 TYPE(elbuf_struct_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 INTEGER I,J,K,M1,M2,IG,IGTYP,KAD,ITYP,NG,JFT,JLT,NEL,
62 . NB8,NFT,NUVAR,IRB,NV
63 my_real dtn,dtr,dtrb1,dtrb2,dt
64 TYPE(g_bufel_),POINTER :: GBUF
65C----------------------------------------------------------
66
67 IF ((nodadt==0).AND.(idtmins/=2)) THEN
68C
69 DO ng=1,ngroup
70 ityp = iparg(5,ng)
71 nel = iparg(2,ng)
72 nft = iparg(3,ng)
73 jft = 1
74 jlt = min(nvsiz,nel)
75 gbuf => elbuf_tab(ng)%GBUF
76 IF (ityp == 6) THEN
77C
78C--------> Boucle sur les elements ressort -------
79 DO i=jft,jlt
80 j = i + nft
81 ig = ipart(2,ipartr(j))
82 igtyp = igeo(11,ig)
83 nuvar = nint(geo(25,ig))
84 nv = nuvar*(i-1) + 1
85 IF (igtyp==45) THEN
86C
87C--------> Calcul pas de temps nodal RB1 -------
88 irb = nint(gbuf%VAR(nv + 37))
89 IF (irb > 0) THEN
90 m1 = npby(1,irb)
91 ELSE
92 m1 = ixr(2,j)
93 ENDIF
94 dtrb1 = dtfac1(11)*sqrt(two*ms(m1)/max(em20,stifn(m1)))
95 IF (in(m1) > 0) THEN
96 dtrb1 = min(dtrb1,dtfac1(11)*sqrt(two*in(m1)/max(em20,stifr(m1))))
97 ENDIF
98C
99C--------> Calcul pas de temps nodal RB2 -------
100 irb = nint(gbuf%VAR(nv + 38))
101 IF (irb > 0) THEN
102 m2 = npby(1,irb)
103 ELSE
104 m2 = ixr(3,j)
105 ENDIF
106 dtrb2 = dtfac1(11)*sqrt(two*ms(m2)/max(em20,stifn(m2)))
107 IF (in(m2) > 0) THEN
108 dtrb2 = min(dtrb2,dtfac1(11)*sqrt(two*in(m2)/max(em20,stifr(m2))))
109 ENDIF
110C
111C--------> Calcul pas de temps du Joint -------
112 dt = min(dtrb1,dtrb2)
113 IF(dt<dt2t) THEN
114 dt2t=dt
115 ityptst=11
116 IF (dtrb1 < dtrb2) THEN
117 neltst = itab(m1)
118 ELSE
119 neltst = itab(m2)
120 ENDIF
121 ENDIF
122
123 ENDIF
124 ENDDO
125C
126 ENDIF
127 ENDDO
128C
129 ENDIF
130C
131 RETURN
132
133 END
#define my_real
Definition cppsort.cpp:32
subroutine joint_elem_timestep(ms, in, stifn, stifr, ixr, ipart, ipartr, igeo, geo, npby, iparg, elbuf_tab, dt2t, neltst, ityptst, nrbody, itab)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21