36
37
38
42
43
44
45#include "implicit_f.inc"
46
47
48
49#include "param_c.inc"
50#include "com04_c.inc"
51
52
53
54 INTEGER :: NUPARAM,NUMTABL,MAT_ID
55 INTEGER ,DIMENSION(NUMTABL) :: ITABLE,TABLE_ID
56 my_real ,
DIMENSION(NPROPM) :: pm
57 my_real ,
DIMENSION(NUPARAM),
INTENT(INOUT) :: uparam
58 TYPE(TTABLE) ,DIMENSION(NTABLE) :: TABLE
59 CHARACTER(LEN=NCHARTITLE) :: TITR
60
61
62
63 INTEGER :: I,J,FUNC,FUND,NDIM,NPOINT
64 my_real :: e11,n12,n21,nu,c1,ssp,kmax,kini,dx,dy,slope,rho,
65 . fscale1,fscale2,fscalet,det,a11,a12,a22,xint,yint
66
67 func = itable(1)
68 fund = itable(2)
69 n12 = uparam(3)
70 fscale1 = uparam(11)
71 fscale2 = uparam(12)
72 fscalet = uparam(13)
73
74 IF (func > 0) THEN
75 ndim = table(func)%NDIM
76 npoint = SIZE(table(func)%X(1)%VALUES)
77 dx = table(func)%X(1)%VALUES(2) - table(func)%X(1)%VALUES(1)
78 dy = table(func)%Y%VALUES(2) - table(func)%Y%VALUES(1)
79 kini = fscale1 * dy / dx
80 kmax = kini
81 DO i = 3,npoint
82 j = i-1
83 dx = table(func)%X(1)%VALUES(i) - table(func)%X(1)%VALUES(j)
84 dy = table(func)%Y%VALUES(i) - table(func)%Y%VALUES(j)
85 slope = fscale1 * dy / dx
86 kmax =
max(kmax, slope)
87 END DO
88
89 IF (fund > 0) THEN
90 ndim = table(fund)%NDIM
91 npoint = SIZE(table(fund)%X(1)%VALUES)
92 dx = table(fund)%X(1)%VALUES(2) - table(fund)%X(1)%VALUES(1)
93 dy = table(fund)%Y%VALUES(2) - table(fund)%Y%VALUES(1)
94 kini = fscale2 * dy / dx
95 kmax =
max(kmax, kini)
96 DO i = 3,npoint
97 j = i-1
98 dx = table(fund)%X(1)%VALUES(i) - table(fund)%X(1)%VALUES(j)
99 dy = table(fund)%Y%VALUES(i) - table(fund)%Y%VALUES(j)
100 slope = fscale2 * dy / dx
101 kmax =
max(kmax, slope)
102 END DO
103
104
105 CALL table_inters(table,func,fund,fscale1,fscale2,xint,yint)
106
107 IF (xint == zero .or. yint == zero) THEN
108 CALL ancmsg(msgid=3081 ,msgtype=msgerror,anmode=aninfo_blind_2,
109 . i1 = mat_id,
110 . i2 = table_id(1),
111 . i3 = table_id(2),
112 . c1 = titr )
113 ENDIF
114 uparam(18) = xint
115 uparam(19) = yint
116 END IF
117
118 uparam(1) = kini
119 uparam(22) = kmax
120
121
122 END IF
123
124 RETURN
subroutine table_inters(table, func1, func2, fac1, fac2, xint, yint)
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)