35 SUBROUTINE inspcnd(ISPCOND ,IGRNOD ,KXSP ,IXSP ,
36 . NOD2SP ,ITAB ,ICODE ,ISKEW ,ISKN ,
37 . SKEW ,XFRAME ,X ,ISPSYM ,ISPTAG ,
38 . PM ,GEO ,IPART ,IPARTSP )
47#include "implicit_f.inc"
59 INTEGER ISPCOND(NISPCOND,*),
60 . KXSP(NISP,*),IXSP(KVOISPH,*),NOD2SP(*),
61 . ITAB(*),ICODE(*),ISKEW(*),ISKN(LISKN,*),
62 . ispsym(nspcond,*),isptag(*),ipart(lipart1,*),ipartsp(*)
65 . skew(lskew,*),xframe(nxframe,*),x(3,*),
66 . pm(npropm,*),geo(npropg,*)
68 TYPE (GROUP_) ,
DIMENSION(NGRNOD) :: IGRNOD
73 . K,K2,K3,IFR,NC,ICSP,,IC1,IC2,IC,J6(6),
74 . ISLIDE,IMAT,IPROP,IPRT
77 . tx,ty,tz,ux,uy,uz,vx,vy,vz,wx,wy,wz,nw,nt,ps,
78 . dd,ox,oy,oz,xi,yi,zi,di,mp
98 IF (icode(inod)/=0)
THEN
104 iskn(2,j)=iskn(2,isk)
105 iskn(3,j)=iskn(3,isk)
122 WRITE(iout,*)
' SPH SYMMETRY CONDITIONS INITIALIZATION :'
123 WRITE(iout,*)
' -------------------------------------- '
131 ux=xframe(3*(icsp-1)+1,ifr)
132 uy=xframe(3*(icsp-1)+2,ifr)
133 uz=xframe(3*(icsp-1)+3,ifr)
144 dd=(xi-ox)*ux+(yi-oy)*uy+(zi-oz)*uz
149 mp =get_u_geo(1,iprop)
151 di =get_u_geo(6,iprop)
153 IF(di==0.) di=(sqrt(2.)*vol)**untiers
155 isptag(n)=isptag(n)+1
161 DO 888 j=1,igrnod(igrs)%NENTITY
162 inod=igrnod(igrs)%ENTITY(j)
165 IF(ic/=0.AND.iskn(1,isk)/=0)
THEN
173 . anmode=aninfo_blind_1,
181 j6(2)=(ic1-4*j6(1))/2
182 j6(3)=(ic1-4*j6(1)-2*j6(2))
184 j6(5)=(ic2-4*j6(4))/2
185 j6(6)=(ic2-4*j6(4)-2*j6(5))
193 . msgtype=msgwarning,
194 . anmode=aninfo_blind_2,
217 IF(abs(ps)<em20)
THEN
219 . msgtype=msgwarning,
220 . anmode=aninfo_blind_2,
230 ic1=j6(1)*4+j6(2)*2+j6(3)
233 icode(inod)=my_or(ic,icode(inod))
236 k=7*j6(3)+4*j6(2)+j6(1)
243 nw=sqrt(wx*wx+wy*wy+wz*wz)
246 . msgtype=msgwarning,
247 . anmode=aninfo_blind_2)
256 nt=sqrt(tx*tx+ty*ty+tz*tz)
276 ic1=j6(1)*4+j6(2)*2+j6(3)
279 icode(inod)=my_or(ic,icode(inod))
282 skew(k,isk)=xframe(k,ifr)
291 icode(inod)=my_or(ic,icode(inod))
subroutine inspcnd(ispcond, igrnod, kxsp, ixsp, nod2sp, itab, icode, iskew, iskn, skew, xframe, x, ispsym, isptag, pm, geo, ipart, ipartsp)
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)