48
49
50
51
52
53
54
55
56
57
58
59
61 USE elbufdef_mod
62 USE intbufdef_mod
67
68
69
70#include "implicit_f.inc"
71#include "comlock.inc"
72
73
74
75#include "com01_c.inc"
76#include "com04_c.inc"
77#include "param_c.inc"
78#include "vect01_c.inc"
79#include "scr17_c.inc"
80#include "task_c.inc"
81#include "inter22.inc"
82
83
84
85 INTEGER IXS(NIXS,*),IPARG(NPARG,NGROUP),NALE(*),NODFT,ITASK,NV46,NODLT,IPM(NPROPMI,NUMMAT)
86
87 my_real x(3,*),v(3,*),vr(3,*),msnf(*)
88 TYPE(ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
89 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
90
91
92
93 INTEGER N, NG, NF1,
94 . ISOLNOD, NEL,
95 . ISTRA
96 INTEGER IPLA
97 INTEGER IALEFVM_FLG, IMAT,NSG,NVC
99 . bid
100
101 TYPE(G_BUFEL_) ,POINTER :: GBUF
102 TYPE(L_BUFEL_) POINTER
103
104INTEGER :: NIN,NBF,NBL,tNB
105
106
107
109
110
111
112
113
114
115
116 nin = 1
117 bid = zero
118
119
120
121 nbf = 1+itask*
nb/nthread
122 nbl = (itask+1)*
nb/nthread
124 tnb = nbl-nbf+1
125
127
128 IF(int22/=0)THEN
130 ENDIF
131
132
133
134
135
136
138
141
142 DO ng=itask+1,ngroup,nthread
144 1 iparg ,ng ,
145 2 mtn ,nel ,nft ,iad ,ity ,
146 3 npt ,jale ,ismstr ,jeul ,jtur ,
147 4 jthe ,jlag ,jmult ,jhbe
148 5 nvaux ,jpor ,jcvt ,jclose ,ipla ,
149 6 irep ,iint ,igtyp ,israt ,isrot ,
150 7 icsen ,isorth ,isorthg ,ifailure,jsms
151 . )
152 gbuf => elbuf_tab(ng)%GBUF
153 IF (iparg(8,ng) == 1) cycle
154 IF (jlag == 1 .OR. ity>2) cycle
155 nsg = iparg(10,ng)
156 nvc = iparg(19,ng)
157 isolnod = iparg(28,ng)
158 istra = iparg(44,ng)
159 jsph = 0
160 isph2sol = 0
161 ipartsph = iparg(69,ng)
162 lft = 1
163 llt = nel
164 nf1 = nft+1
165 IF(ity == 1 .AND. isolnod == 4)THEN
166
167
168 ELSEIF(ity == 1 .AND. isolnod /= 4)THEN
169 lbuf => elbuf_tab(ng)%BUFLY(1)%LBUF(1,1,1)
170 imat = ixs(1,nft+lft)
171 ialefvm_flg = ipm(251,imat)
172 IF (ialefvm_flg <= 1) cycle
174 1 ixs , nv46 , ale_connect , ialefvm_flg
175
176 3 x , gbuf%TAG22 ,nel )
178 1 ixs , ialefvm_flg,
179 2 gbuf%MOM, gbuf%VOL, gbuf%RHO,
180 3 ipm , gbuf%TAG22
181 4 lbuf%SSP,gbuf%SIG , nel )
182 ELSEIF (ity == 2 .AND. jmult == 0) THEN
183
184 ELSEIF(ity == 2 .AND. jmult /= 0)THEN
185
186 ENDIF
187 enddo
188 endif
189
191
192
193
194 DO n=nodft,nodlt
199 ENDDO
200
201#include "vectorize.inc"
202
203 DO n=nodft,nodlt
204 IF(msnf(n)<=zero)cycle
205 IF(nale(n)==0)cycle
206 v(1,n) = v(1,n) / msnf(n)
207 v(2,n) = v(2,n) / msnf(n)
208 v(3,n) = v(3,n) / msnf(n)
209 ENDDO
210 IF (iroddl/=0) THEN
211#include "vectorize.inc"
212
213 DO n=nodft,nodlt
214 IF(nale(n)==0)cycle
215 vr(1,n) = zero
216 vr(2,n) = zero
217 vr(3,n) = zero
218 ENDDO
219 ENDIF
220
223
224 RETURN
subroutine alefvm_scheme(ixs, ialefvm_flg, mom, vol, rho, ipm, iad22, ssp, sig, nel)
subroutine alefvm_sfint3(ixs, nv46, ale_connect, ialefvm_flg, ipm, iparg, ng, x, iad22, nel)
subroutine alefvm_sfint3_int22(ixs, nv46, itask, nbf, nbl, nin)
type(alefvm_buffer_), target alefvm_buffer
type(alefvm_param_), target alefvm_param
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)