OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
law90_upd.F File Reference
#include "implicit_f.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine law90_upd (iout, titr, mat_id, uparam, ipm, func_id, npc, pld, pm, nfunct)

Function/Subroutine Documentation

◆ law90_upd()

subroutine law90_upd ( integer iout,
character(len=nchartitle) titr,
integer mat_id,
uparam,
integer, dimension(npropmi), target ipm,
integer, dimension(nfunct) func_id,
integer, dimension(*) npc,
pld,
pm,
integer, intent(in) nfunct )

Definition at line 34 of file law90_upd.F.

36C-----------------------------------------------
37C M o d u l e s
38C-----------------------------------------------
39 USE message_mod
40 USE table_mod
42C-----------------------------------------------
43C I m p l i c i t T y p e s
44C-----------------------------------------------
45#include "implicit_f.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "param_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 CHARACTER(LEN=NCHARTITLE) :: TITR
54 INTEGER ,INTENT(IN) :: NFUNCT
55 INTEGER MAT_ID,IOUT,ID_F1,ID_F2
56 INTEGER NPC(*), FUNC_ID(NFUNCT), IPM(NPROPMI)
57 my_real
58 . uparam(*),pld(*),pm(npropm)
59! TYPE(TTABLE) TABLE(*)
60 TARGET ipm
61 INTEGER, DIMENSION(:), POINTER :: IFUNC
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER NFUNC,I,J
66 INTEGER IPRINT, LP,IndexDesign0
67
68 my_real
69 . stiff,stiffc,stifft, emax_curve, emin_curve,eini_curve,
70 . stiffmin,stiffmax,stiffini,stfavg,scalefac,e0,
71 . epsmax,ec_max,emax,g,c1,nu
72
73 COMMON /mincfprt/iprint, lp
74 COMMON /index_sqp/indexdesign0
75C=======================================================================
76 nfunc = ipm(10)
77 ifunc => ipm(10+1:10+nfunc)
78C=======================================================================
79c
80 emax_curve = zero
81 emin_curve = ep20
82 eini_curve = zero
83 epsmax = one
84 DO j = 1, nfunc
85 scalefac= uparam(10 + nfunc + j )
86 CALL func_slope(ifunc(j),scalefac,npc,pld,stiffmin,stiffmax,stiffini,stfavg)
87 emax_curve = max(emax_curve, stiffmax )
88 emin_curve = min(emin_curve, stiffmin)
89 eini_curve = max(eini_curve, stiffini)
90 ENDDO ! NFUNC
91 e0 = uparam(1)
92 IF(e0 < eini_curve) THEN
93 e0 = eini_curve
94 uparam(1) = e0
95 CALL ancmsg(msgid=865, msgtype=msgwarning, anmode=aninfo_blind_1,
96 . i1=mat_id,
97 . c1=titr,
98 . r1=e0)
99 ENDIF
100 IF(emax_curve <= e0) THEN
101 emax = e0
102 ELSE
103 emax = min(emax_curve,hundred*e0 ) !
104 ENDIF
105 ec_max = max(e0,emax)
106 uparam(11 + 2*nfunc) = emax
107 uparam(12 + 2*nfunc) = epsmax
108 nu = uparam(5)
109 c1 = e0/three/(one - two*nu)
110 g = half*e0/(one + nu)
111 pm(20) = e0
112 pm(22) = g
113 pm(24) = ec_max
114 pm(32) = c1
115!
116 WRITE(iout,1000)
117 WRITE(iout,1001) trim(titr),mat_id,90
118 WRITE(iout,1002) emax
119 WRITE(iout,1003) ec_max
120c----------------
121 RETURN
1221000 FORMAT(
123 & 5x,' TABULATED NON LINEAR VISCO ELASTIC LAW',/,
124 & 5x,' ----------------------------- --------',//)
1251001 FORMAT(/
126 & 5x,a,/,
127 & 5x,'MATERIAL NUMBER . . . . . . . . . . . .=',i10/,
128 & 5x,'MATERIAL LAW. . . . . . . . . . . . . .=',i10/)
1291002 FORMAT(
130 & 5x,'MAXIMUM YOUNG''S MODULUS. . . . . . . .=',1pg20.13/)
1311003 FORMAT(
132 & 5x,'YOUNG''S MODULUS FOR HG COMPUTE . . . .=',1pg20.13/)
133
#define my_real
Definition cppsort.cpp:32
subroutine func_slope(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
Definition func_slope.F:37
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889