OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dtnodamp.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!|| dtnodamp ../engine/source/time_step/dtnodamp.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.F
27!||--- uses -----------------------------------------------------
28!|| groupdef_mod ../common_source/modules/groupdef_mod.F
29!||====================================================================
30 SUBROUTINE dtnodamp(ITAB ,MS ,IN ,STIFN ,STIFR ,DT2T,
31 1 WEIGHT ,IGRNOD ,DAMPR ,ISTOP ,
32 2 I_DAMP_RDOF_TAB,ICONTACT ,IXC ,X )
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE groupdef_mod
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41#include "comlock.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com01_c.inc"
46#include "com04_c.inc"
47#include "scr18_c.inc"
48#include "com08_c.inc"
49#include "param_c.inc"
50C-----------------------------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER ITAB(*),WEIGHT(*),ISTOP,
54 . I_DAMP_RDOF_TAB(*),ICONTACT(*),IXC(NIXC,*)
55C REAL
56 my_real dt2t, dmast, dinert, stifn(*), stifr(*),
57 . ms(*) ,in(*) ,dampr(nrdamp,*),x(3,*)
58C-----------------------------------------------
59 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63 INTEGER N,I,J,ISK,IGR,ND,K,L,LL
64 my_real FACTB,DAMPBR,DAMPAR,D_TSTART,D_TSTOP,DAMPT,
65 . dt2n(numnod),bb,coeff,stif_mod,dt_cible,eta,beta,
66 . alpha,dampa0
67C----------------------------------------------------------
68
69C--------> TAG des elements
70 DO nd=1,ndamp
71 IF (dampr(20,nd)>0) THEN
72 DO i=1,numelc
73 DO j=1,4
74 k=ixc(j+1,i)
75 IF (icontact(k)==1) THEN
76 DO l=1,4
77 ll = ixc(l+1,i)
78 IF (ll/=k) THEN
79 i_damp_rdof_tab(ll) = dampr(19,nd)
80 ENDIF
81 END DO
82 ENDIF
83 ENDDO
84 ENDDO
85 ENDIF
86 ENDDO
87
88 DO nd=1,ndamp
89C-------->
90 IF (ncycle==0) THEN
91 alpha = dtmin1(11)/dtfac1(11)
92 IF (alpha>0) THEN
93 dampa0=max(dampr(9,nd),dampr(11,nd),dampr(13,nd))
94 dampr(9,nd)=min(dampr(9,nd),1/alpha)
95 dampr(11,nd)=min(dampr(11,nd),1/alpha)
96 dampr(13,nd)=min(dampr(13,nd),1/alpha)
97 dampar=max(dampr(9,nd),dampr(11,nd),dampr(13,nd))
98 IF (dampa0/=dampar) THEN
99 print *,"WARNING ALPHA reduced to",1/alpha
100 ENDIF
101 ENDIF
102 ENDIF
103C-------->
104 igr = nint(dampr(2,nd))
105 isk = nint(dampr(15,nd))
106 factb = one
107 d_tstart = dampr(17,nd)
108 d_tstop = dampr(18,nd)
109 IF (tt>=d_tstart .AND. tt<=d_tstop) THEN
110 dampar = max(dampr(9,nd),dampr(11,nd),dampr(13,nd))
111 dampbr = max(dampr(10,nd),dampr(12,nd),dampr(14,nd))
112C-------->
113 DO i=1,igrnod(igr)%NENTITY
114 n=igrnod(igr)%ENTITY(i)
115 IF(stifr(n)<=zero)THEN
116 istop=-itab(n)
117 ELSEIF(in(n)>zero)THEN
118 dt2n(n)=dtfac1(11)*sqrt(two*in(n)/stifr(n))
119 ENDIF
120 ENDDO
121C-------->
122 DO i=1,igrnod(igr)%NENTITY
123 n=igrnod(igr)%ENTITY(i)
124 dampt = min(dt1,dt2n(n))*factb
125 beta = min(dampbr,dampt)
126 alpha = dampar
127 bb = beta+half*half*alpha*dt2n(n)*dt2n(n)
128 eta = sqrt(bb*bb + dt2n(n)*dt2n(n)) - bb
129 IF (idtmin(11)==3) THEN
130 dt_cible = eta+0*max(eta,dtmin1(11))
131 ELSE
132 dt_cible = eta
133 ENDIF
134 coeff = (one+(2*beta/dt_cible))/((1-half*alpha*dt_cible))
135 IF (dampr(19,nd)/=0) THEN
136 IF ((i_damp_rdof_tab(n)+icontact(n))/=0) THEN
137 stifr(n) = stifr(n)*coeff
138 ENDIF
139 ENDIF
140 ENDDO
141C-------->
142 ENDIF
143
144 END DO
145
146C
147 RETURN
148 END
#define my_real
Definition cppsort.cpp:32
subroutine dtnodamp(itab, ms, in, stifn, stifr, dt2t, weight, igrnod, dampr, istop, i_damp_rdof_tab, icontact, ixc, x)
Definition dtnodamp.F:33
#define alpha
Definition eval.h:35
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21