OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
law77_upd.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!|| law77_upd ../starter/source/materials/mat/mat077/law77_upd.F
25!||--- called by ------------------------------------------------------
26!|| updmat ../starter/source/materials/updmat.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!|| func_slope ../starter/source/tools/curve/func_slope.F
30!||--- uses -----------------------------------------------------
31!|| message_mod ../starter/share/message_module/message_mod.F
32!|| table_mod ../starter/share/modules1/table_mod.F
33!||====================================================================
34 SUBROUTINE law77_upd(TITR ,MAT_ID ,NUPARAM ,MAT_PARAM ,
35 . UPARAM ,NFUNC ,IFUNC ,NPC ,PLD )
36C-----------------------------------------------
37C M o d u l e s
38C-----------------------------------------------
39 USE message_mod
40 USE matparam_def_mod
41 USE table_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER MAT_ID,NFUNC,NUPARAM
51 INTEGER STF,SNPC
52 INTEGER ,DIMENSION(NFUNC) :: IFUNC
53 INTEGER :: NPC(*)
54 my_real pld(*)
55 my_real uparam(nuparam)
56 CHARACTER(LEN=NCHARTITLE) :: TITR
57 TYPE(matparam_struct_) :: MAT_PARAM
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 INTEGER :: I,J,K,II,JJ,NDIM,NLOAD,NULOAD,NPT,NEPSP,FUNC_ID,
62 . func_t,func_c,func_s,icas,iconv,
63 . npt_trac,npt_comp,npt_shear,nptmax,ifun_nup,ifx,ify,stat,
64 . len,ix0,iy0,iflag,iflag0,nf,itens,ichk,ic1,ic2,ibid
65 my_real :: xint,yint,emax,e0,epsmax,eps0,epst1,fac,deri,
66 . x0,y0,x1,y1,dx,dy,stiffmin,stiffmax,stiffini,stiffavg
67 INTEGER ,DIMENSION(:) ,ALLOCATABLE :: SIZE
68 my_real ,DIMENSION(:) ,ALLOCATABLE :: x_comp,y_comp
69 my_real ,DIMENSION(NFUNC) :: rate,yfac
70C=======================================================================
71 nload = int(uparam(7))
72 nuload = int(uparam(8))
73 e0 = uparam(2)
74 epsmax = uparam(4)
75 emax = uparam(2*nfunc + 12)
76 itens = uparam(2*nfunc + 13)
77c
78 DO i = 1,nfunc
79 rate(i) = uparam(i + 8)
80 yfac(i) = uparam(i + 8 + nfunc)
81 END DO
82C=======================================================================
83 ibid = mat_param%ILAW
84 iflag = 0
85c When Emax=0 we consider the max curve slope.
86 IF (emax == zero) THEN
87 DO k=1,nfunc
88 func_id = ifunc(k)
89 fac = yfac(k)
90 CALL func_slope(func_id,fac,npc,pld,stiffmin,stiffmax,stiffini,stiffavg)
91 uparam(2*nfunc + 12) = stiffmax
92 uparam(3) = (stiffmax - e0)/stiffmax
93 CALL ancmsg(msgid=1219,msgtype=msginfo,anmode=aninfo_blind_1,
94 . i1=mat_id,
95 . c1=titr,
96 . r1=emax)
97 END DO
98c IF (STIFFMAX < E0) IFLAG0 = 1
99 ENDIF ! emax
100c automatic modification of EPST1 and E0
101 eps0 = one
102 iflag = 0
103 iflag0= 0
104 epst1 = one
105 DO k=1,nload
106 func_id = ifunc(k)
107 ichk = 0
108 IF (func_id > 0 ) THEN
109 fac = yfac(k)
110 ic1 = npc(func_id)
111 ic2 = npc(func_id+1)
112C loading function
113 x0 = pld(ic1)
114 DO ii = ic1,ic2-4,2
115 jj = ii+2
116 dx = pld(jj) - x0
117 dy = pld(jj+1) - pld(ii+1)
118 y0 = fac*pld(ii+1)
119 y1 = fac*pld(jj+1)
120 deri = fac * dy / dx
121 x1 = pld(jj)
122 IF(x1 > zero .AND. ichk == 0 ) THEN
123 ichk = 1
124C check of initial rigidity
125 IF(deri > e0) THEN
126 iflag0 = 1
127 e0 = deri
128 IF(emax <e0)emax = e0
129 ENDIF
130 ENDIF
131 IF ( deri >= emax .AND. x0 > zero) THEN
132 eps0 = min(eps0, x0 )
133 iflag = 1
134 IF(x0 == eps0) THEN
135 epst1 = min(epst1,abs(eps0 - y0/emax))
136 ENDIF
137 ENDIF
138 x0 = pld(jj)
139 ENDDO
140 ENDIF
141 ENDDO ! NLOAD
142C
143 IF (iflag == 1) THEN
144 e0 = min(e0, emax)
145 uparam(3) = (emax - e0)/epst1
146 uparam(4) = eps0
147 CALL ancmsg(msgid=864,msgtype=msginfo,anmode=aninfo_blind_1,
148 . i1=mat_id,
149 . c1=titr,
150 . r1=eps0)
151 ENDIF
152 IF (iflag0 == 1) THEN
153 e0 = min(e0, emax)
154 uparam(3) = (emax - e0)/epst1
155 uparam(2) = e0
156 CALL ancmsg(msgid=865,msgtype=msgwarning,anmode=aninfo_blind_1,
157 . i1=mat_id,
158 . c1=titr,
159 . r1=e0)
160 ENDIF
161c--------------------------------------------------------
162 RETURN
163 END
#define my_real
Definition cppsort.cpp:32
subroutine func_slope(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
Definition func_slope.F:37
subroutine law77_upd(titr, mat_id, nuparam, mat_param, uparam, nfunc, ifunc, npc, pld)
Definition law77_upd.F:36
#define min(a, b)
Definition macros.h:20
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