5 &(lihbor,klog,it1,it2,it3,lvmac,ielmx,
6 & lambd0,spheri,mesh,t1,t2,optass,produc,equa,mesh2d)
117 INTEGER,
INTENT(IN) :: IELMX,OPTASS,PRODUC,KLOG,LVMAC
118 INTEGER,
INTENT(IN) :: LIHBOR(*)
119 DOUBLE PRECISION,
INTENT(IN) :: LAMBD0
120 LOGICAL,
INTENT(IN) :: SPHERI
121 CHARACTER(LEN=20) :: EQUA
122 TYPE(bief_mesh),
INTENT(INOUT) :: MESH
123 TYPE(bief_obj),
INTENT(INOUT) :: T1,T2,IT1,IT2,IT3
124 TYPE(bief_mesh),
INTENT(INOUT),
OPTIONAL :: MESH2D
128 INTEGER I,IELEM,NELEM,NELMAX,NPTFR,NPOIN,IELM,IPLAN,I3D
130 INTEGER LV,NDP,IDP,I1,I2,I3,NPOIN2
131 INTEGER NPTFR2,NELEM2,NELMAX2,NELEB2,NELEB
132 INTEGER NELCOU,IELEM3D
134 DOUBLE PRECISION X2,X3,Y2,Y3
152 IF(ielm.EQ.41.OR.ielm.EQ.51)
THEN 158 ELSEIF(ielm.EQ.11.OR.ielm.EQ.31)
THEN 166 WRITE(
lu,*)
'UNEXPECTED ELEMENT IN INBIEF:',ielm
174 ALLOCATE(mesh%WI8(nelmax*ndp))
175 ALLOCATE(mesh%TI8(npoin))
184 CALL parini(mesh%NHP%I,mesh%NHM%I,mesh%INDPU%I,
185 & npoin2,mesh%NACHB%I,nplan,mesh,
186 & mesh%NB_NEIGHB,mesh%NB_NEIGHB_SEG,
187 & nelem2,mesh%IFAPAR%I,
modass)
191 CALL bief_allvec(2,mesh%NB_NEIGHB_PT,
'NBNGPT',0,1,0,mesh)
192 CALL bief_allvec(2,mesh%LIST_SEND ,
'LSSEND',0,1,0,mesh)
193 CALL bief_allvec(2,mesh%NH_COM ,
'NH_COM',0,1,0,mesh)
194 CALL bief_allvec(2,mesh%NB_NEIGHB_PT_SEG,
'NBNGSG',0,1,0,mesh)
195 CALL bief_allvec(2,mesh%LIST_SEND_SEG,
'LSSESG',0,1,0,mesh)
196 CALL bief_allvec(2,mesh%NH_COM_SEG ,
'NH_CSG',0,1,0,mesh)
197 CALL bief_allvec(1,mesh%BUF_SEND ,
'BUSEND',0,1,0,mesh)
198 CALL bief_allvec(1,mesh%BUF_RECV ,
'BURECV',0,1,0,mesh)
200 CALL bief_allvec(1,mesh%BUF_SEND_ERR ,
'BUSEND_ERR',0,1,0,mesh)
201 CALL bief_allvec(1,mesh%BUF_RECV_ERR ,
'BURECV_ERR',0,1,0,mesh)
216 IF(ielm.EQ.11.OR.ielm.EQ.41.OR.ielm.EQ.51)
THEN 217 CALL voisin(mesh%IFABOR%I,nelem2,nelmax2,ielm,mesh%IKLE%I,
219 & npoin2,mesh%NACHB%I,mesh%NBOR%I,nptfr2,it1%I,it2%I)
221 ELSEIF(ielm.NE.31)
THEN 222 WRITE(
lu,*)
'UNEXPECTED ELEMENT IN INBIEF:',ielm
229 IF(ielm.EQ.11.OR.ielm.EQ.41.OR.ielm.EQ.51)
THEN 239 CALL elebd(mesh%NELBOR%I,mesh%NULONE%I,mesh%KP1BOR%I,
240 & mesh%IFABOR%I,mesh%NBOR%I,mesh%IKLE%I,
242 & mesh%IKLBOR%I,nelem2,nelmax2,npoin2,nptfr2,ielm,
243 & lihbor,klog,mesh%ISEG%I,
244 & it1%I,it2%I,it3%I,mesh%NELEBX,mesh%NELEB)
254 CALL voisin31(mesh%IFABOR%I,nelem,nelmax,ielm,mesh%IKLE%I,
255 & mesh%IKLE%MAXDIM1,npoin,mesh%NBOR%I,nptfr,
256 & lihbor,klog,mesh%INDPU%I,iklestr,neleb2)
258 CALL elebd31(mesh%NELBOR%I,mesh%NULONE%I,mesh%IKLBOR%I,
259 & mesh%IFABOR%I,mesh%NBOR%I,mesh%IKLE%I,
260 & nelem,neleb,nelmax,npoin,nptfr,ielm)
262 ELSEIF(ielm.EQ.41)
THEN 266 CALL eleb3d(mesh%IKLE%I,mesh%NBOR%I,
267 & mesh%NELBOR%I,mesh%IKLBOR%I,
268 & mesh%NELEB,mesh%NELEBX,
269 & mesh%NULONE%I,nelmax2,npoin2,nplan,nplan-1,nptfr2)
271 ELSEIF(ielm.EQ.51)
THEN 275 IF(
PRESENT(mesh2d))
THEN 278 CALL eleb3dt(mesh%IKLE%I,mesh%NBOR%I,mesh%NELBOR%I,
279 & mesh2d%NELBOR%I,mesh%IKLBOR%I,
280 & mesh%NELEB,mesh%NELEBX,mesh%NULONE%I,nelmax2,
281 & npoin2,nplan,nplan-1,nptfr2,
282 & mesh2d%IKLBOR%I,mesh2d%NELEB,mesh2d%NELEBX)
284 WRITE(
lu,*)
'ARGUMENT MESH2D SHOULD BE ADDED TO INBIEF' 285 WRITE(
lu,*)
'FOR A CALL WITH IELM=51' 290 ELSEIF(ielm.NE.11)
THEN 292 WRITE(
lu,*)
'INBIEF UNEXPECTED ELEMENT: ',ielm
306 201
FORMAT(1x,
'INBIEF (BIEF): VECTOR MACHINE',/,1x,
307 &
'WITH VECTOR LENGTH :',1i6,
308 &
' (ACCORDING TO YOUR DATA OR IN THE DICTIONNARY OF KEY-WORDS)')
309 CALL veclen(lv,ndp,mesh%IKLE%I,nelem,nelmax,npoin,t1%R)
312 301
FORMAT(1x,
'THIS LENGTH IS REDUCED TO ',1i4,
' BY THE NUMBERING 313 &OF THE ELEMENTS (SEE STBTEL DOCUMENTATION)')
318 401
FORMAT(1x,
'INBIEF (BIEF): NOT A VECTOR MACHINE',
319 &
' (ACCORDING TO YOUR DATA)')
330 IF(spheri.AND.ielm.NE.11.AND.ielm.NE.41)
THEN 332 399
FORMAT(1x,
'INBIEF (BIEF) : ELEMENT NOT IMPLEMENTED WITH',/,1x,
333 &
'MERCATOR PROJECTION:',1i3)
342 CALL latitu(t2%R,mesh%COSLAT%R,mesh%SINLAT%R,
343 & lambd0,mesh%Y%R,npoin2)
346 IF(ielm.EQ.11.OR.ielm.EQ.41)
THEN 356 i3d=(iplan-1)*npoin2+i
357 t1%R(i3d)=mesh%X%R(i3d)
364 CALL pttoel(mesh%XEL,t1,mesh)
365 CALL pttoel(mesh%YEL,t2,mesh)
373 CALL pttoel(mesh%XEL,mesh%X,mesh)
374 CALL pttoel(mesh%YEL,mesh%Y,mesh)
383 CALL ov_2(
'X=X-Y ',mesh%XEL%R,idp,
385 & mesh%XEL%R,1 , 0.d0 , nelmax , nelem )
386 CALL ov_2(
'X=X-Y ',mesh%YEL%R,idp,
388 & mesh%YEL%R,1 , 0.d0 , nelmax , nelem )
391 CALL ov(
'X=C ', x=mesh%XEL%R, c=0.d0, dim1=nelem)
392 CALL ov(
'X=C ', x=mesh%YEL%R, c=0.d0, dim1=nelem)
397 IF(
PRESENT(mesh2d))
THEN 398 CALL longitu(mesh2d%XEL%R,mesh%COSLAT%R,mesh2d%IKLE%I,
400 nelcou = (nplan-1)*nelmax2
403 ielem3d=(iplan-1)*nelmax2+ielem
405 mesh%XEL%R(ielem3d) =mesh2d%XEL%R(ielem)
406 mesh%XEL%R(ielem3d+nelcou )=mesh2d%XEL%R(ielem+nelmax2)
407 mesh%XEL%R(ielem3d+2*nelcou)=mesh2d%XEL%R(ielem+2*nelmax2)
409 mesh%XEL%R(ielem3d+3*nelcou)=mesh%XEL%R(ielem3d)
410 mesh%XEL%R(ielem3d+4*nelcou)=mesh%XEL%R(ielem3d+nelcou)
411 mesh%XEL%R(ielem3d+5*nelcou)=mesh%XEL%R(ielem3d+2*nelcou)
415 CALL longitu(mesh%XEL%R,mesh%COSLAT%R,mesh%IKLE%I,
439 CALL geoelt(mesh%SURDET%R,mesh%SURFAC%R,
440 & mesh%XEL%R ,mesh%YEL%R ,nelem,nelmax,ielm)
449 i1 = mesh%IKLE%I(ielem)
450 i2 = mesh%IKLE%I(ielem+nelmax)
451 i3 = mesh%IKLE%I(ielem+2*nelmax)
452 x2 = - mesh%X%R(i1) + mesh%X%R(i2)
453 x3 = - mesh%X%R(i1) + mesh%X%R(i3)
454 y2 = - mesh%Y%R(i1) + mesh%Y%R(i2)
455 y3 = - mesh%Y%R(i1) + mesh%Y%R(i3)
456 mesh%SURDET%R(ielem) = 1.d0 / (x2*y3 - x3*y2)
461 ELSEIF(ielm.EQ.41.OR.ielm.EQ.51.OR.ielm.EQ.31)
THEN 467 x2 = mesh%XEL%R(ielem+nelmax)
468 x3 = mesh%XEL%R(ielem+2*nelmax)
469 y2 = mesh%YEL%R(ielem+nelmax)
470 y3 = mesh%YEL%R(ielem+2*nelmax)
471 mesh%SURFAC%R(ielem) = 0.5d0 * (x2*y3 - x3*y2)
475 WRITE(
lu,*)
'UNEXPECTED ELEMENT IN INBIEF:',ielm
487 CALL normab(mesh%XNEBOR%R,mesh%YNEBOR%R,
488 & mesh%XSGBOR%R,mesh%YSGBOR%R,
489 & mesh%DISBOR%R,mesh%SURFAC%R,nelmax,mesh%NELBOR%I,
490 & mesh%NULONE%I,mesh%LGSEG%R,nptfr,mesh,
491 & mesh%XEL%R,mesh%YEL%R,mesh%IKLBOR%I,
492 & mesh%NELEBX,mesh%NELEB)
504 CALL stoseg(mesh%IFABOR%I,nelem,nelmax,nelmax,ielmx,mesh%IKLE%I,
505 & mesh%NBOR%I,nptfr,mesh%GLOSEG%I,mesh%GLOSEG%MAXDIM1,
506 & mesh%ELTSEG%I,mesh%ORISEG%I,mesh%NSEG,
507 & mesh%NELBOR%I,mesh%NULONE%I,
508 & mesh%KNOLG%I,mesh%IKLBOR%I,mesh%NELEBX,mesh%NELEB)
510 ELSEIF(ielm.EQ.41)
THEN 512 CALL stoseg41(mesh%IFABOR%I,nelmax,ielmx,mesh%IKLE%I,mesh%NBOR%I,
513 & mesh%GLOSEG%I,mesh%GLOSEG%MAXDIM1,
514 & mesh%ELTSEG%I,mesh%ORISEG%I,
515 & mesh%NELBOR%I,mesh%NULONE%I,
516 & nelmax2,nelem2,nptfr2,npoin2,nplan,mesh%KNOLG%I,
518 & mesh%IKLBOR%I,mesh%NELEBX,mesh%NELEB)
520 ELSEIF(ielm.EQ.51)
THEN 522 IF(
PRESENT(mesh2d))
THEN 525 CALL stoseg51(mesh%IFABOR%I,nelmax,ielmx,
526 & mesh%IKLE%I,mesh%NBOR%I,
527 & mesh%GLOSEG%I,mesh%GLOSEG%MAXDIM1,
528 & mesh%ELTSEG%I,mesh%ORISEG%I,
529 & mesh2d%NELBOR%I,mesh2d%NULONE%I,
530 & nelmax2,nelem2,nptfr2,npoin2,nplan,mesh%KNOLG%I,
531 & mesh2d%NSEG,mesh2d%IKLBOR%I,mesh2d%NELEB,
534 WRITE(
lu,*)
'ARGUMENT MESH2D SHOULD BE ADDED TO INBIEF' 535 WRITE(
lu,*)
'FOR A CALL WITH IELM=51' 542 WRITE(
lu,*)
'ELEMENT ',ielm,
' NOT IMPLEMENTED FOR SEGMENTS' 552 CALL voisin31(mesh%IFABOR%I,nelem,nelmax,ielm,mesh%IKLE%I,
553 & mesh%IKLE%MAXDIM1,npoin,mesh%NBOR%I,nptfr,
554 & lihbor,klog,mesh%INDPU%I,iklestr,1)
559 IF(ncsize.GT.1.AND.ielm.EQ.11)
THEN 565 & mesh%NH_COM_SEG%DIM1,mesh%NB_NEIGHB_SEG,
566 & mesh%NB_NEIGHB_PT_SEG%I,
567 & mesh%GLOSEG%I,mesh%GLOSEG%DIM1,
568 & mesh%KNOLG%I,npoin)
572 IF(ielm.EQ.11.AND.ielmx.EQ.13)
THEN 573 CALL comp_fac(mesh%ELTSEG%I,mesh%ORISEG%I,mesh%IFABOR%I,nelem,
583 IF(ielm.EQ.11.AND.produc.EQ.2)
THEN 585 CALL fropro(mesh%NBOR%I,mesh%IKLE%I,
586 & nelem,nelmax,npoin,mesh%NPMAX,nptfr,ielm,
587 & mesh%IKLEM1%I,mesh%LIMVOI%I,optass,produc,mxptvs,
588 & it1%I,mesh%GLOSEG%I,mesh%GLOSEG%DIM1,mesh%NSEG)
596 IF(ielm.EQ.11.AND.ielm.NE.ielmx)
THEN 597 IF(mesh%IKLE%DIM2.NE.
bief_nbpel(ielmx,mesh))
THEN 599 101
FORMAT(1x,
'INBIEF (BIEF): WRONG DIMENSION OF IKLE',/,1x,
600 &
'FOR AN ELEMENT WITH TYPE :',1i6)
604 CALL comp_ikle(mesh%IKLE%I,mesh%IKLBOR%I,
605 & mesh%ELTSEG%I,mesh%NBOR%I,mesh%NELBOR%I,
606 & mesh%NULONE%I,ielmx,nelem,nelmax,npoin,nptfr,
607 & mesh%NELEB,mesh%NELEBX)
614 IF(ielm.NE.ielmx)
THEN 615 CALL comp_seg(nelem,nelmax,ielmx,mesh%IKLE%I,mesh%GLOSEG%I,
616 & mesh%GLOSEG%MAXDIM1,mesh%ELTSEG%I,mesh%ORISEG%I,
626 IF(equa(1:15).EQ.
'SAINT-VENANT VF')
THEN 629 & mesh%IKLE%I,npoin,mesh%ELTSEG%I,
630 & mesh%ORISEG%I,nelem,mesh%NSEG,
631 & mesh%JMI%I,mesh%CMI%R,mesh%GLOSEG%I,
632 & mesh%IFABOR%I,mesh)
640 IF(equa(1:15).EQ.
'SAINT-VENANT VF')
THEN 642 CALL infcel(mesh%X%R,mesh%Y%R,
643 & mesh%NUBO%I,mesh%VNOIN%R,npoin,
644 & nelem,mesh%NSEG,mesh%CMI%R,
645 & mesh%AIRST%R,mesh%GLOSEG%I,
646 & mesh%COORDG%R,mesh%ELTSEG%I,
647 & mesh%ORISEG%I,mesh%IFABOR%I)
651 CALL vector(t1,
'=',
'MASBAS ',11,
652 & 1.d0,t2,t2,t2,t2,t2,t2,mesh,.false.,t2)
653 IF(ncsize.GT.1)
CALL parcom(t1,2,mesh)
657 CALL hloc(npoin,mesh%NSEG,nelem,mesh%NUBO%I,mesh%VNOIN%R,t1%R,
658 & mesh%DTHAUT%R,mesh,mesh%ELTSEG%I,mesh%IFABOR%I)
662 CALL gradp(npoin,mesh%NELMAX,mesh%IKLE%I,mesh%SURFAC%R,
663 & mesh%X%R,mesh%Y%R,mesh%DPX%R,mesh%DPY%R)
672 & mesh%IKLE%I,npoin2,nelem2,
673 & nelmax,mesh%KNOLG%I,it1%I,mesh,nplan,ielmx)
subroutine geoelt(SURDET, SURFAC, XEL, YEL, NELEM, NELMAX, IELM)
subroutine comp_ikle(IKLE, IKLBOR, ELTSEG, NBOR, NELBOR, NULONE, IELM, NELEM, NELMAX, NPOIN, NPTFR, NELEB, NELEBX)
subroutine ov(OP, X, Y, Z, C, DIM1)
subroutine longitu(XEL, COSLAT, IKLE, NELMAX, NELEM)
integer function bief_nbpts(IELM, MESH)
subroutine hloc(NPOIN, NSEG, NELEM, NUBO, VNOCL, AIRS, DTHAUT, MESH, ELTSEG, IFABOR)
subroutine parini(NHP, NHM, INDPU, NPOIN2, NACHB, NPLAN, MESH, NB_NEIGHB, NB_NEIGHB_SEG, NELEM2, IFAPAR, MODASS)
integer function bief_nbpel(IELM, MESH)
subroutine voisin31(IFABOR, NELEM, NELMAX, IELM, IKLE, SIZIKL, NPOIN, NBOR, NPTFR, LIHBOR, KLOG, INDPU, IKLESTR, NELEB2)
subroutine make_eltcar(ELTCAR, IFAC, IKLE, NPOIN2, NELEM2, NELMAX, KNOLG, ISCORE, MESH, NPLAN, IELM)
subroutine bief_allvec(NAT, VEC, NOM, IELM, DIM2, STATUT, MESH)
subroutine ov_2(OP, X, DIMX, Y, DIMY, Z, DIMZ, C, DIM1, NPOIN)
subroutine comp_seg(NELEM, NELMAX, IELM, IKLE, GLOSEG, MAXSEG, ELTSEG, ORISEG, NSEG)
subroutine stoseg51(IFABOR, NELMAX, IELM, IKLE, NBOR, GLOSEG, MAXSEG, ELTSEG, ORISEG, NELBOR, NULONE, NELMAX2, NELEM2, NPTFR2, NPOIN2, NPLAN, KNOLG, NSEG2D, IKLBOR, NELEB, NELEBX)
subroutine comp_nh_com_seg(ELTSEG, DIM1ELTSEG, NH_COM_SEG, DIM1NHCOM, NB_NEIGHB_SEG, NB_NEIGHB_PT_SEG, GLOSEG, DIMGLO, KNOLG, NPOIN)
subroutine fropro(NBOR, IKLE, NELEM, NELMAX, NPOIN, NPMAX, NPTFR, IELM, IKLEM1, LIMVOI, OPTASS, PRODUC, MXPTVS, T1, GLOSEG, SIZGLO, NSEG)
subroutine eleb3d(IKLE3, NBOR, NELBOR, IKLBOR, NELEB, NELEBX, NULONE, NELEM2, NPOIN2, NPLAN, NETAGE, NPTFR)
subroutine comp_fac(ELTSEG, ORISEG, IFABOR, NELEM, NPOIN, IFAC)
subroutine pttoel(XEL, X, MESH)
subroutine checkmesh(MESH, NPOIN)
subroutine centre_mass_seg(X, Y, COORD_G, IKLE, NPOIN, ELTSEG, ORISEG, NELEM, NSEG, JMI, CMI, GLOSEG, IFABOR, MESH)
subroutine latitu(YDIST, COSLAT, SINLAT, LAMBD0, Y, NPOIN)
subroutine vector(VEC, OP, FORMUL, IELM1, XMUL, F, G, H, U, V, W, MESH, MSK, MASKEL, LEGO, ASSPAR)
subroutine infcel(XX, YY, NUBO, VNOIN, NPOIN, NELEM, NSEG, CMI, AIRST, GLOSEG, COORD_G, ELTSEG, ORISEG, IFABOR)
subroutine elebd31(NELBOR, NULONE, IKLBOR, IFABOR, NBOR, IKLE, NELEM, NELEB, NELMAX, NPOIN, NPTFR, IELM)
subroutine parcom(X, ICOM, MESH)
subroutine veclen(LV, NDP, IKLE, NELEM, NELMAX, NPOIN, V)
subroutine normab(XNEBOR, YNEBOR, XSGBOR, YSGBOR, DISBOR, SURFAC, NELMAX, NELBOR, NULONE, LGSEG, NPTFR, MESH, XEL, YEL, IKLBOR, NELEBX, NELEB)
integer function bief_nbmpts(IELM, MESH)
subroutine inbief(LIHBOR, KLOG, IT1, IT2, IT3, LVMAC, IELMX, LAMBD0, SPHERI, MESH, T1, T2, OPTASS, PRODUC, EQUA, MESH2D)
subroutine stoseg41(IFABOR, NELMAX, IELM, IKLE, NBOR, GLOSEG, MAXSEG, ELTSEG, ORISEG, NELBOR, NULONE, NELMAX2, NELEM2, NPTFR2, NPOIN2, NPLAN, KNOLG, NSEG2D, IKLBOR, NELEBX, NELEB)
subroutine voisin(IFABOR, NELEM, NELMAX, IELM, IKLE, SIZIKL, NPOIN, NACHB, NBOR, NPTFR, IADR, NVOIS)
subroutine eleb3dt(IKLE3, NBOR, NELBOR, NELBOR2D, IKLBOR, NELEB, NELEBX, NULONE, NELEM2, NPOIN2, NPLAN, NETAGE, NPTFR, IKLBOR2D, NELEB2D, NELEBX2D)
integer function bief_nbseg(IELM, MESH)
subroutine stoseg(IFABOR, NELEM, NELMAX, NELMAX2, IELM, IKLE, NBOR, NPTFR, GLOSEG, MAXSEG, ELTSEG, ORISEG, NSEG, NELBOR, NULONE, KNOLG, IKLBOR, NELEBX, NELEB)
subroutine elebd(NELBOR, NULONE, KP1BOR, IFABOR, NBOR, IKLE, SIZIKL, IKLBOR, NELEM, NELMAX, NPOIN, NPTFR, IELM, LIHBOR, KLOG, ISEG, T1, T2, T3, NELEBX, NELEB)
subroutine gradp(NS, NT, IKLE, AIRT, X, Y, DPX, DPY)