OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m18law.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "com08_c.inc"
#include "param_c.inc"
#include "scr18_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine m18law (pm, volu, eint, theta, deltax, tf, npf, dt2t, neltst, ityptst, ipm, sti, voln, mat, ngl, conde, nel, ity, idt_therm, dt_therm)

Function/Subroutine Documentation

◆ m18law()

subroutine m18law ( pm,
volu,
eint,
theta,
deltax,
tf,
integer, dimension(*) npf,
dt2t,
integer neltst,
integer ityptst,
integer, dimension(npropmi,*) ipm,
sti,
voln,
integer, dimension(*) mat,
integer, dimension(*) ngl,
conde,
integer, intent(in) nel,
integer, intent(in) ity,
integer, intent(in) idt_therm,
intent(inout) dt_therm )

Definition at line 30 of file m18law.F.

36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C C o m m o n B l o c k s
46C-----------------------------------------------
47#include "com08_c.inc"
48#include "param_c.inc"
49#include "scr18_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER, INTENT(IN) :: NEL
54 INTEGER, INTENT(IN) :: ITY
55 INTEGER, INTENT(IN) :: IDT_THERM
56 INTEGER NPF(*),IPM(NPROPMI,*),MAT(*),NGL(*)
57 INTEGER NELTST,ITYPTST
58 my_real, INTENT(INOUT) :: dt_therm
59 my_real :: dt2t
60
62 . pm(npropm,*), volu(*), eint(*), theta(*), deltax(*), tf(*),
63 . sti(*),voln(mvsiz), conde(*)
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER I, IFUNC, NPOINT, ITFUN, IKFUN, MX
68 my_real a(mvsiz), b(mvsiz),
69 . dtx(mvsiz), sph(mvsiz), rho0, espe, dtde, t0, bid,
70 . timescal,tscal,escal,kscal,
71 . sph_1,a_1,b_1
72C-----------------------------------------------
73C=======================================================================
74 mx = mat(1)
75 sph_1=pm(69,mx)
76 a_1 =pm(75,mx)
77 b_1 =pm(76,mx)
78 DO i=1,nel
79 voln(i)=volu(i)
80 sph(i)=sph_1
81 a(i) =a_1
82 b(i) =b_1
83 ENDDO
84
85 DO i=1,nel
86 ifunc = ipm(12,mx)
87 IF(ifunc/=0)THEN
88 rho0=pm( 1,mx)
89 npoint=(npf(ifunc+1)-npf(ifunc))/2
90 tscal = pm(42,mx)
91 escal = pm(43,mx)
92 espe = escal * eint(i) / rho0
93 CALL interp(tf(npf(ifunc)),espe,npoint,theta(i),dtde)
94 theta(i) = tscal*theta(i)
95 sph(i) = rho0 / max(em20,dtde)
96 ELSE
97 theta(i)=eint(i)/sph(i)
98 ENDIF
99 ENDDO
100
101 itfun = ipm(11,mx)
102 IF(itfun/=0)THEN
103 t0=pm(79,mx)
104 timescal = pm(41,mx)*tt
105 npoint=(npf(itfun+1)-npf(itfun))/2
106 DO i=1,nel
107 CALL interp(tf(npf(itfun)),timescal,npoint,theta(i),bid)
108 theta(i) = t0*theta(i)
109 eint(i) = sph(i)*theta(i)
110 ENDDO
111 ENDIF
112
113 DO i=1,nel
114 ikfun = ipm(13,mx)
115 IF (ikfun /= 0) THEN
116 tscal = theta(i) / pm(42,mx)
117 kscal = pm(44,mx)
118 npoint=(npf(ikfun+1)-npf(ikfun))/2
119 CALL interp(tf(npf(ikfun)),tscal,npoint,a(i),bid)
120 a(i) = kscal * a(i)
121 b(i) = zero
122 ENDIF
123 dtx(i)=half*deltax(i)**2*sph(i)/(a(i)+b(i)*theta(i))
124 ENDDO
125
126C--------------------------
127C THERMAL TIME STEP
128C--------------------------
129 IF(idt_therm == 1)THEN
130 DO i=1,nel
131 IF(dtx(i)<dt_therm) dt_therm = dtx(i)
132 conde(i) = four*volu(i)*(a(i)+b(i)*theta(i))/deltax(i)*deltax(i)
133c CONDE(I) = CONDE(I)*OFF(I)
134 ENDDO
135 ENDIF
136
137 DO i=1,nel
138 ! dt2, nelts, itypts remplaces par dt2t, neltst, ityptst
139 IF(dtx(i)>dt2t) cycle
140 dt2t=dtx(i)
141 neltst =ngl(i)
142 ityptst=ity
143 ENDDO
144
145 DO i=1,nel
146 sti(i)=zero
147 END DO
148
149 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine interp(tf, tt, npoint, f, tg)
Definition interp.F:35
#define max(a, b)
Definition macros.h:21