52#include "implicit_f.inc"
65 INTEGER,
INTENT(INOUT) :: (LIPART1,)
69 INTEGER :: STAT,I,J,LEN1,LEN2,NUM,P,N
70 INTEGER :: K,ADD,COMPT,NB_PART,F2,,,PID,COMPT_STACK_TOT,COMPT_STACK
71 INTEGER :: COMPT_STACK_REMOV,,COMPT_PCOMP,COMPT_PCOMP_REMOV
72 INTEGER,
DIMENSION(:),
ALLOCATABLE :: NUMGEOSTACK1_TEMP,NUMGEOSTACK2_TEMP
73 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: IPM_TEMP,IGEO_TEMP
74 CHARACTER(LEN=NCHARTITLE) TITR
76 my_real,
DIMENSION(:,:),
ALLOCATABLE :: pm_temp,geo_temp
77 my_real,
DIMENSION(:,:,:),
ALLOCATABLE :: ddw_temp
84 ALLOCATE (pm_r2r(nummat+npart+1),stat=stat)
85 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1=
'PM_R2R')
87 pm_r2r(i) = pm(npropm*(i-1)+20)
90 IF (ipid==0) nsubdom = 1
96 IF (ipid==0) n = iddom
120 compt_pcomp_remov = 0
122 compt_stack_remov = 0
130 igtyp =
igeo(npropgi*(ipartl(2,k)-1)+11)
131 IF (igtyp==51) compt_stack_tot = compt_stack_tot + 1
132 IF (igtyp==52) compt_pcomp_tot = compt_pcomp_tot + 1
136 IF ((igtyp==11).OR.(igtyp==16))
THEN
139 ELSEIF (igtyp.EQ.52)
THEN
142 compt_pcomp_remov = compt_pcomp_remov + 1
143 ELSEIF (igtyp.EQ.51)
THEN
146 compt_stack_remov = compt_stack_remov + 1
151 compt_pcomp = compt_pcomp_tot - compt_pcomp_remov
152 IF (compt_pcomp > 0) ipart_pcompp = 1
153 compt_stack = compt_stack_tot - compt_stack_remov
154 IF (compt_stack > 0) ipart_stack = 1
156 IF (compt==0)
GOTO 150
164 ALLOCATE (ipm_temp(npropmi,nummat+nb_part),stat=stat)
165 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1=
'IPM_TEMP')
166 ALLOCATE (pm_temp(npropm,nummat+nb_part),stat=stat)
167 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1=
'PM_TEMP')
168 ALLOCATE (ddw_temp(2,2,nummat+nb_part+1),stat=stat)
169 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1=
'DDW_TEMP')
179 ipm_temp(j,i)=
ipm(npropmi*(i-1)+j)
185 pm_temp(j,i)=pm(npropm*(i-1)+j)
192 ddw_temp(j,l,i)=ddweights(j,l,i)
199 ddw_temp(j,l,nummat+nb_part+1)=ddweights(j,l,nummat+1)
206 IF (num<=ipm_temp(1,i)) num=ipm_temp(1,i)
220 pm_temp(1,nummat)= 1e-20
221 pm_temp(19,nummat) =zero
222 pm_temp(20,nummat) = pm_temp(20,f2)
223 pm_r2r(nummat)= pm_temp(20,f2)
224 pm_temp(21,nummat) = pm_temp(21,f2)
225 pm_temp(32,nummat) = pm_temp(32,f2)
226 pm_temp(70,nummat) =zero
227 pm_temp(71,nummat) =zero
228 pm_temp(72,nummat) =zero
229 pm_temp(75,nummat) = pm_temp(75,f2)
230 pm_temp(76,nummat) = pm_temp(76,f2)
231 pm_temp(89,nummat) = pm_temp(1,nummat)
232 pm_temp(100,nummat) = pm_temp(100,f2)
236 pm_temp(1,nummat)= 1e-20
237 pm_temp(19,nummat) =zero
238 pm_temp(70,nummat) =zero
239 pm_temp(71,nummat) =zero
240 pm_temp(72,nummat) =zero
241 pm_temp(89,nummat) = pm_temp(1,nummat)
243 DO i=1,
igeo(npropgi*(ipartl(2,k)-1)+4)
244 f2 =
igeo(npropgi*(ipartl(2,k)-1)+100+i)
245 alphai = geo(npropg*(ipartl(2,k)-1)+300+i)
246 pm_temp(20,nummat) = pm_temp(20,nummat) + alphai*pm_temp(20,f2)
247 pm_r2r(nummat)= pm_r2r(nummat) + alphai*pm_temp(20,f2)
248 pm_temp(21,nummat) = pm_temp(21,nummat) + alphai*pm_temp(21,f2)
249 pm_temp(32,nummat) = pm_temp(32,nummat) + alphai*pm_temp(32,f2)
250 pm_temp(75,nummat) = pm_temp(75,nummat) + alphai*pm_temp(75,f2)
251 pm_temp(76,nummat) = pm_temp(76,nummat) + alphai*pm_temp(76,f2)
252 pm_temp(100,nummat) = pm_temp(100,nummat) + alphai*pm_temp(100,f2)
257 ipm_temp(1,nummat)= num
258 ipm_temp(2,nummat)= 0
259 titr =
"Multidomains void material"
260 CALL fretitl(titr,ipm_temp(npropmi-ltitr,nummat),ltitr)
262 WRITE(iout,1300) num,pm_temp(1,nummat)
263 . ,pm_temp(20,nummat),pm_temp(21,nummat),ipartl(4,k)
274 len1 = npropmi*nummat
277 DEALLOCATE(
ipm,pm,ddweights)
278 ALLOCATE (
ipm(len1),stat=stat)
279 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo, msgtype=msgerror, c1=
'IPM')
280 ALLOCATE (pm(len2),stat=stat)
281 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo, msgtype=msgerror, c1=
'PM')
286 ipm(npropmi*(i-1)+j)=ipm_temp(j,i)
292 pm(npropm*(i-1)+j)=pm_temp(j,i)
299 ddweights(j,l,i)=ddw_temp(j,l,i)
304 DEALLOCATE(ipm_temp,pm_temp,ddw_temp)
311 pid =
igeo(npropgi*(ipartl(2,k)-1)+1)
317 CALL my_alloc (igeo_temp,npropgi,numgeo+nb_part)
318 CALL my_alloc (geo_temp,npropg,numgeo+nb_part)
319 CALL my_alloc (numgeostack1_temp,numgeo+nb_part)
320 CALL my_alloc (numgeostack2_temp,numstack)
324 numgeostack1_temp(:)=0
325 numgeostack2_temp(:)=0
331 igeo_temp(j,i)=
igeo(npropgi*(i-1)+j)
337 geo_temp(j,i)=geo(npropg*(i-1)+j)
352 IF (num.LE.igeo_temp(1,i)) num=igeo_temp(1,i)+1
360 igeo_temp(1,numgeo)=num
361 geo_temp(1,numgeo)=geo_temp(1,f2)
362 numgeostack1_temp(numgeo)=0
364 titr =
"Multidomains void property"
365 CALL fretitl(titr,igeo_temp(npropgi-ltitr,numgeo),ltitr)
367 WRITE(iout,1400) num,geo_temp(1,numgeo),ipartl(4,k)
375 len1 = npropgi*numgeo
379 CALL my_alloc (
igeo,len1)
380 CALL my_alloc (geo,len2)
385 igeo(npropgi*(i-1)+j)=igeo_temp(j,i)
391 geo(npropg*(i-1)+j)=geo_temp(j,i)
403 DEALLOCATE(igeo_temp,geo_temp,numgeostack1_temp,numgeostack2_temp)
417 . //
' MULTIDOMAINS SPECIAL TREATMENTS '/
418 .
' --------------------------------- '/)
420 & 5x,40hvoid material created ,/,
421 & 5x,40h ----------- ,/,
422 & 5x,40hmaterial
id . . . . . . . . . . . . .=,i10/,
423 & 5x,40hdensity . . . . . . . . . . . . . . .=,e12.4/,
424 & 5x,40hyoung
'S MODULUS . . . . . . . . . . . .=,E12.4/,
425 & 5X,40HPOISSON's ratio . . . . . . . . . . . .=,e12.4/,
426 & 5x,40happlied on part . . . . . . . . .
428 & 5x,40hvoid property created ,/,
429 & 5x,40h ----------- ,/,
430 & 5x,40hproperty
id . . . . . . . . . . . . .=,i10/,
431 & 5x,40hthickness. . . . . . . . . . . . . . .=,e12.4/,
432 & 5x,40happlied on part . . . . . . . . . . . =,i10//)
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)