36
37
38
40 USE elbufdef_mod
41
42
43
44#include "implicit_f.inc"
45
46
47
48#include "vect01_c.inc"
49#include "mvsiz_p.inc"
50#include "com01_c.inc"
51#include "com04_c.inc"
52#include "sphcom.inc"
53#include "scr17_c.inc"
54#include "param_c.inc"
55#include "task_c.inc"
56
57
58
59
61 . mas(*) ,pm(npropm,*),geo(npropg,*),x(3,*),d(3,*)
62 INTEGER IPARG(NPARG,*),IXS(NIXS,*),EL2FA(*),NBF,IPART(LIPART1,*),
63 . IPARTSP(*),ISPH3D
64 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
65
66
67
68
70 . evar(mvsiz),
71 . off, p, vonm2, vonm, s1, s2, s12, s3, VALUE,thk0,a0,al0,
72 . rho0,xx1,xx2,xx3,yy1,yy2,yy3,zz1,zz2,zz3
73 INTEGER I, NG, NEL, ISS, ISC,
74 . IADD, N, J, MLW,
75 . ISTRAIN,NN, K1, K2,JTURB,MT,IMID, IALEL,IPID,
76 . N1,N2,N3,N4,
77 . NN1,NN2,NN3,NN4,NN5,NN6,NN7,,NN9,NN10,
78 . OFFSET,NEL_OLD,ITY_OLD,NFT_FA,N_FA,
79 . INOD, ISOLNOD, IPRT
80 TYPE(G_BUFEL_) ,POINTER :: GBUF
81
82 nn1 = 1
83 nn2 = 1
84 nn3 = nn2 + numels
85 nn4 = nn3 + isph3d*(numsph+maxpjet)
86
87
88
89 nel_old = 0
90 ity_old = 0
91 DO 490 ng=1,ngroup
93 2 mlw ,nel ,nft ,iad ,ity ,
94 3 npt ,jale ,ismstr ,jeul ,jtur ,
95 4 jthe ,jlag ,jmult ,jhbe ,jivf ,
96 5 nvaux ,jpor ,jcvt ,jclose ,jplasol ,
97 6 irep ,iint ,igtyp ,israt ,isrot ,
98 7 icsen ,isorth ,isorthg ,ifailure,jsms )
99 isolnod = iparg(28,ng)
100 IF (ispmd == 0) THEN
101 IF (ity/=ity_old) THEN
102 nel_old = 0
103 ity_old= ity
104 ENDIF
105 nft_fa = nel_old
106 nel_old = nel_old + nel
107 ENDIF
108 DO offset = 0,nel-1,nvsiz
109 nft =iparg(3,ng) + offset
110 iad =iparg(4,ng)
111 lft=1
112 llt=
min(nvsiz,nel-offset)
113 IF (ispmd == 0) THEN
114 nft_fa = nel_old - nel + offset
115 ELSE
116 nft_fa = nft
117 ENDIF
118
119
120
121 IF(ity == 1)THEN
122 gbuf => elbuf_tab(ng)%GBUF
123 ialel=iparg(7,ng)+iparg(11,ng)
124 DO 130 i=lft,llt
125 n = i + nft
126 n_fa = i + nft_fa
127 IF(el2fa(nn2+n_fa)/=0)THEN
128 IF (mlw == 0 .or. mlw == 13 .or. igtyp == 0) THEN
129 VALUE = zero
130 ELSEIF(ialel == 0)THEN
131 mt=ixs(1,n)
132 VALUE=pm(89,mt)*gbuf%VOL(i)
133 ELSE
134 off =
min(gbuf%OFF(i),one)
135 VALUE=gbuf%RHO(i)*gbuf%VOL(i)*off
136 ENDIF
137 IF( nfilsol /= 0 .AND. gbuf%G_FILL /= 0 )
138 . VALUE = VALUE * gbuf%FILL(i)
139 IF (isolnod == 16) THEN
140 VALUE = fourth*VALUE
141 mas(el2fa(nn2+n_fa)) = VALUE
142 mas(el2fa(nn2+n_fa)+1) = VALUE
143 mas(el2fa(nn2+n_fa)+2) = VALUE
144 mas(el2fa(nn2+n_fa)+3) = VALUE
145 ELSE
146 mas(el2fa(nn2+n_fa)) = VALUE
147 ENDIF
148 ENDIF
149 130 CONTINUE
150
151 ELSEIF(isph3d == 1 .AND. ity == 51)THEN
152
153
154
155 gbuf => elbuf_tab(ng)%GBUF
156 ialel=iparg(7,ng)+iparg(11,ng)
157 DO 140 i=lft,llt
158 n = i + nft
159 n_fa = i + nft_fa
160 IF(el2fa(nn3+n_fa)/=0)THEN
161 IF(ialel == 0)THEN
162 iprt=ipartsp(n)
163 mt =ipart(1,iprt)
164 VALUE=pm(89,mt)*gbuf%VOL(i)
165 ELSE
166 off =
min(gbuf%OFF(i),one)
167 VALUE=gbuf%RHO(i)*gbuf%VOL(i)*off
168 ENDIF
169 mas(el2fa(nn3+n_fa)) = VALUE
170 ENDIF
171 140 CONTINUE
172
173 ELSE
174 ENDIF
175
176
177
178 END DO
179 490 CONTINUE
180
181
182 RETURN
subroutine initbuf(iparg, ng, mtn, llt, nft, iad, ity, npt, jale, ismstr, jeul, jtur, jthe, jlag, jmult, jhbe, jivf, mid, jpor, jcvt, jclose, jpla, irep, iint, igtyp, israt, isrot, icsen, isorth, isorthg, ifailure, jsms)