29!||====================================================================
30 SUBROUTINE aleno(NN , SURF_NODES, NNB, ITABINV,
31 2 TAGE, TAGVENT ,TAGNODBR, T_MONVOLN)
39#include "implicit_f.inc"
48 . itabinv(*), tage(*), tagvent(numnod),
49 . tagnodbr(numnod),surf_nodes(nn,4)
54 INTEGER (NUMNOD),IAD1,,I1,I2,I3,I4,J,K,KK,NA,NB,NC,NC2,, IADFIN, JAD1, NALL, NODESURF(4*NN)
55 INTEGER IADCH(NUMNOD),CHAIN(2,4*NN),(4*NN),IP2(0:3),INVP2(15)
71 nodesurf(iad1) = surf_nodes(i,k)
85 IF(j == nodesurf(iad1+k-1)) j=0
125 IF(j == nodesurf(iad1+k-1)) j=0
130 nall=nall*tagnodbr(j)
133 IF(nall == 1)
GO TO 10
138 IF(j == nodesurf(iad1+k-1)) j=0
147 IF(jad1 /= iad1)
THEN
150 j = nodesurf(jad1+kk)
152 IF(j == nodesurf(jad1+kk-1)) j=0
163 IF(nc == na .and. na == nb)
THEN
183 IF(j == nodesurf(iad1+k-1)) j=0
195 ELSEIF(tage(i) /= 0)
THEN
215 IF (i4 /= 0) itag(i4)=1
216 ELSEIF(tage(i) == 1)
THEN
221 ELSEIF(tage(i) == 2)
THEN
225 IF (i4 /= 0) tagvent(i4)=1
226 ELSEIF(tage(i) == 3)
THEN
231 ELSEIF(tage(i) == 4)
THEN
236 ELSEIF(tage(i) == 5)
THEN
240 IF (i4 /= 0) tagvent(i4)=1
252 ALLOCATE(t_monvoln%NODES(nnb))
257 t_monvoln%NODES(nnb)=i
274 . VX3 , VY3 , VZ3 , VX1 , VY1,
275 . VZ1 , XB0 , YB0 , ZB0 ,
276 . LX , LY , LZ, IBUF , IBUFA, TAGELA,
283#include "implicit_f.inc"
287#include "com04_c.inc"
291 INTEGER,
INTENT(IN) :: NELA, MONVID
292 INTEGER,
DIMENSION(3, NELA),
INTENT(IN) :: ELEMA
293 INTEGER,
INTENT(IN) :: IBUF(*), IBUFA(*), TAGELA(*)
294 my_real,
INTENT(INOUT) :: LX, LY, LZ
295 CHARACTER(LEN=nchartitle),
INTENT(IN) :: TITR
296 my_real x(3,numnod), vx3, vy3, vz3, vx1, vy1, vz1, xb0, yb0, zb0
300 INTEGER I, ITAG(NUMNOD), I1, I2, I3
302 .
norm, ss, vx2, vy2, vz2, lxmax, lymax, xx, yy, zz, xl, yl,
303 . lzmax, zl, lx_old, ly_old, lz_old
307 norm=sqrt(vx3**2+vy3**2+vz3**2)
311 . anmode=aninfo_blind_1,
319 ss=vx3*vx1+vy3*vy1+vz3*vz1
323 norm=sqrt(vx1**2+vy1**2+vz1**2)
327 . anmode=aninfo_blind_1,
346 IF (tagela(i)>0)
THEN
369 xl=(xx-xb0)*vx1+(yy-yb0)*vy1+(zz-zb0)*vz1
370 yl=(xx-xb0)*vx2+(yy-yb0)*vy2+(zz-zb0)*vz2
371 zl=(xx-xb0)*vx3+(yy-yb0)*vy3+(zz-zb0)*vz3
372 lxmax=
max(lxmax,abs(xl))
373 lymax=
max(lymax,abs(yl))
374 lzmax=
max(lzmax,abs(zl))
382 . msgtype=msgwarning,
383 . anmode=aninfo_blind_1,
395 . msgtype=msgwarning,
396 . anmode=aninfo_blind_1,
408 . msgtype=msgwarning,
409 . anmode=aninfo_blind_1,
428 SUBROUTINE fvnodi(NN, SURF_NODES, NNB, ITABINV, T_MONVOLN)
436#include "implicit_f.inc"
440#include "com04_c.inc"
444 INTEGER,
INTENT(IN) :: NN
445 INTEGER,
DIMENSION(NN, 4),
INTENT(IN) :: SURF_NODES
446 INTEGER,
INTENT(OUT) :: NNB
447 INTEGER,
DIMENSION(NUMNOD),
INTENT(INOUT) :: ITABINV
448 TYPE(MONVOL_STRUCT_),
INTENT(INOUT) :: T_MONVOLN
452 INTEGER I, I1, I2, I3, I4, NNS
453 INTEGER,
DIMENSION(:),
ALLOCATABLE :: BUFNODE
454 INTEGER,
DIMENSION(:),
ALLOCATABLE :: ITAG, ITAG_SURFEXT, ITABINV_SURFEXT
455 INTEGER(8) :: VEC_PTR_SURFINT
457 ALLOCATE(itag(numnod), itag_surfext(numnod), itabinv_surfext(numnod))
462 itabinv_surfext(i) = 0
466 ALLOCATE(bufnode(nns))
468 bufnode(i) = t_monvoln%NODES(i)
470 itag_surfext(t_monvoln%NODES(i)) = 1
472 itabinv_surfext(t_monvoln%NODES(i)) = i
484 IF (i4 /= 0) itag(i4)=1
489 CALL intvector_create(vec_ptr_surfint)
492 IF (itag(i) == 1)
THEN
493 IF (itag_surfext(i) /= 1)
THEN
496 itabinv(i) = nnb + nns
497 CALL intvector_push_back(vec_ptr_surfint, i)
499 itabinv(i) = itabinv_surfext(i)
504 DEALLOCATE(t_monvoln%NODES)
505 ALLOCATE(t_monvoln%NODES(nnb + nns))
507 t_monvoln%NODES(i) = bufnode(i)
511 IF(nnb>0)
CALL intvector_copy_to(vec_ptr_surfint, t_monvoln%NODES(nns + 1))
513 CALL intvector_delete(vec_ptr_surfint)
516 DEALLOCATE(itag_surfext)
517 DEALLOCATE(itabinv_surfext)
522!||====================================================================
529 SUBROUTINE fvnodbr(IBUFA, NNA, NNFV, IFV, NB_NODE)
537#include "implicit_f.inc"
541 INTEGER IBUFA(*), NNA, NNFV, IFV, NB_NODE
545 INTEGER I, N, ITAB(NB_NODE)
559 IF(
fvdata(ifv)%IFVNOD(1,i)/=2) cycle
561 fvdata(ifv)%IFVNOD(3,i)=itab(n)
579#include "implicit_f.inc"
583 INTEGER N1, N2, N3, N4
584 my_real X(3,*), NX, NY, NZ
589 . x1, y1, z1, x2, y2, z2, x3, y3, z3, x12, y12, z12,
590 . x13, y13, z13, x4, y4, z4, x24, y24, z24
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine fvverif(nela, elema, x, monvid, vx3, vy3, vz3, vx1, vy1, vz1, xb0, yb0, zb0, lx, ly, lz, ibuf, ibufa, tagela, titr)
subroutine fvnodbr(ibufa, nna, nnfv, ifv, nb_node)
subroutine fvnormal(x, n1, n2, n3, n4, nx, ny, nz)
subroutine fvnodi(nn, surf_nodes, nnb, itabinv, t_monvoln)
subroutine aleno(nn, surf_nodes, nnb, itabinv, tage, tagvent, tagnodbr, t_monvoln)
type(fvbag_data), dimension(:), allocatable fvdata
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)