OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
find_dt_target.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!|| find_dt_target ../common_source/tools/time_step/find_dt_target.f
25!||--- called by ------------------------------------------------------
26!|| add_mass_stat ../starter/source/tools/admas/add_mass_stat.F
28!||====================================================================
29 SUBROUTINE find_dt_target(MS,STIFN,TARGET_DT_TAB,PER_ADM_TAB,DT,TMP,DTSCA,TOTMAS,NVAL,NNOD)
30C-----------------------------------------------
31C I m p l i c i t T y p e s
32C-----------------------------------------------
33#include "implicit_f.inc"
34C-----------------------------------------------
35C A n a l y s e M o d u l e
36C-----------------------------------------------
37C-----------------------------------------------
38C D u m m y A r g u m e n t s
39C-----------------------------------------------
40 INTEGER NVAL,NNOD
42 . ms(*),stifn(*),totmas,target_dt_tab(*),per_adm_tab(*),dtsca,dt(*),tmp(*)
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com01_c.inc"
47#include "com04_c.inc"
48#include "com06_c.inc"
49#include "units_c.inc"
50C-----------------------------------------------
51C L o c a l V a r i a b l e s
52C-----------------------------------------------
53 INTEGER I,N,COMPT,K
54 INTEGER :: CPT
55 my_real sumk,sumk_old,summ,summ_old,per_adm,target_dt,seuil,chunk
56C=======================================================================
57C
58C--------------------------------------------------------------------------------------
59C EXTRACTED FROM ADD_MASS_STAT in starter - used in both starter and engine
60C--------------------------------------------------------------------------------------
61C
62 sumk = zero
63 summ = zero
64 sumk_old = zero
65 summ_old = zero
66 compt = 1
67 seuil = per_adm_tab(1)
68C
69 DO i=1,nnod
70 n=nint(tmp(i))
71 ENDDO
72C
73 DO i=1,nnod
74 IF (i > 1) THEN
75 IF (dt(i) > dt(i-1)) THEN
76 sumk_old = sumk
77 summ_old = summ
78 ENDIF
79 ENDIF
80 n=nint(tmp(i))
81 per_adm = (dt(i)*sumk_old - summ_old)/(max(em20,totmas))
82 IF (i>1) THEN
83 DO WHILE ((per_adm > seuil).AND.(compt<=nval))
84 target_dt_tab(compt) = dtsca*sqrt(two*(totmas*seuil+summ_old)/max(em20,sumk_old))
85 compt = compt+1
86 IF(compt<=nval) seuil = per_adm_tab(compt)
87 ENDDO
88 IF (compt > nval) EXIT
89 ENDIF
90 sumk = sumk + stifn(n)
91 summ = summ + ms(n)
92C-- If threshold are not crossed target dt values must be computed for the last node
93 IF (i==nnod) THEN
94 DO k=compt,nval
95 target_dt_tab(k) = dtsca*sqrt(two*(totmas*seuil+summ)/max(em20,sumk))
96 IF(k+1 <= nval) seuil = per_adm_tab(k+1)
97 ENDDO
98 ENDIF
99 ENDDO
100C
101
102 RETURN
103 END
#define my_real
Definition cppsort.cpp:32
subroutine find_dt_for_targeted_added_mass(ms, stifn, dtsca, igrp_usr, target_dt, percent_addmass, percent_addmass_old, totmas, weight, igrnod, icnds10)
subroutine find_dt_target(ms, stifn, target_dt_tab, per_adm_tab, dt, tmp, dtsca, totmas, nval, nnod)
#define max(a, b)
Definition macros.h:21