36
37
38
40 USE matparam_def_mod
43
44
45
46#include "implicit_f.inc"
47
48
49
50 INTEGER MAT_ID,NFUNC,NUPARAM
51 INTEGER STF,SNPC
52 INTEGER ,DIMENSION(NFUNC) :: IFUNC
53 INTEGER :: NPC(*)
56 CHARACTER(LEN=NCHARTITLE) :: TITR
57 TYPE(MATPARAM_STRUCT_) :: MAT_PARAM
58
59
60
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
70
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)
77
78 DO i = 1,nfunc
79 rate(i) = uparam(i + 8)
80 yfac(i) = uparam(i + 8 + nfunc)
81 END DO
82
83 ibid = mat_param%ILAW
84 iflag = 0
85
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
98
99 ENDIF
100
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)
112
113 x0 = pld(ic1)
114 DO ii = ic1,ic2-4,2
115 jj
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
124
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
142
143 IF (iflag == 1) THEN
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
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
161
162 RETURN
subroutine func_slope(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
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)