The TELEMAC-MASCARET system  trunk
mod_compute_boundary_and_interface.f
Go to the documentation of this file.
1 ! *****************************************
3 ! *****************************************
4 !
5 !***********************************************************************
6 ! PARTEL
7 !***********************************************************************
8 !
9 !BRIEF Computing boundary and interface for partel
10 !
11 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
12  IMPLICIT NONE
13  CONTAINS
14 ! *****************************************
16 ! *****************************************
17  & (nparts, ndp_2d, npoin_p,
18  & nptfr_p, elelg, nelem_p, ikles, knogl,
19  & cut_p, ef_i, ef_ii, nptir_p, nbre_ef_i, knolg, irand,
20  & part_p, nbre_ef)
21 !
22 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
23 !| NPARTS |<--| Number of partitions
24 !| NDP_2D |<--| Number of points per element
25 !| NPOIN_P |<->| Number of point in partition
26 !| NPTFR_P |<->| Number of boundary points in partition
27 !| ELELG |<--| Local to global numbering for elements
28 !| NELEM_P |<--| Number of elements in partition
29 !| IKLES |<->| Connectivity array
30 !| KNOGL |<--| Global to local numbering array
31 !| CUT_P |<->| Global to local numbering for interface points
32 !| EF_I |<->| EF_I(E) is the global label of the interface
33 !| | | finite element number e
34 !| EF_II |<->| EF_II(E) is the local label of the interface
35 !| | | finite element number e
36 !| NPTIR_P |<->| Number of interface points in the partition
37 !| NBRE_EF_I |<->| Number of interface element on the subdomain
38 !| KNOLG |<->| Local to global numbering array
39 !| IRAND |<--| Ipobo array for the partition
40 !| PART_P |<->| List of subdomain each node belongs to
41 !| NBRE_EF |<->| Number of finite element containing I
42 !| | | I is a global label
43 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
44 !
46  USE bief, ONLY : nbmaxnshare
47  USE mod_hash_table
48 !
49 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
50 !
51  INTEGER, ALLOCATABLE, INTENT(INOUT) :: NPOIN_P(:),NPTFR_P(:),
52  & ikles(:), part_p(:,:), ef_i(:,:), ef_ii(:,:),
53  & nptir_p(:), nbre_ef_i(:), knolg(:,:), nbre_ef(:)
54 !
55  TYPE(hash_table), INTENT(INOUT) :: CUT_P
56 !
57  INTEGER, ALLOCATABLE, INTENT(IN) :: ELELG(:,:), NELEM_P(:)
58  INTEGER, ALLOCATABLE, INTENT(IN) :: IRAND(:)
59  INTEGER, INTENT(IN) :: NPARTS, NDP_2D
60  TYPE(hash_table), INTENT(IN) :: KNOGL
61 !
62 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
63 !
64 !
65  INTEGER :: I, J, K, POSI, TEMP, EF, NOEUD
66  INTEGER :: MAX_NPOIN_P, IERR
67  LOGICAL :: INTERFCE
68  INTEGER, ALLOCATABLE :: NBRE_EF_LOC(:)
69 
70  max_npoin_p=maxval(npoin_p)
71 !
72 ! NBRE_EF_LOC(I) : NUMBER OF FINITE ELEMENTS CONTAINING THE POINT I
73 ! ON SUBMESH I
74 ! I IS THE LOCAL LABEL ON SUBMESH I
75  ALLOCATE (nbre_ef_loc(max_npoin_p),stat=ierr)
76  CALL check_allocate(ierr, 'NBRE_EF_LOC')
77 
78  DO i=1,nparts
79  DO j=1,npoin_p(i)
80  nbre_ef_loc(j)=0
81  ENDDO
82 !
83  npoin_p(i)=0
84  nptfr_p(i)=0
85 !
86  DO j=1,nelem_p(i)
87  ef=elelg(j,i)
88  DO k=1,ndp_2d
89  noeud=ikles((ef-1)*3+k)
90  temp=hash_table_get(knogl, noeud, i)
91  nbre_ef_loc(temp)=nbre_ef_loc(temp)+1
92  IF(nbre_ef_loc(temp) .EQ. 1) THEN
93 ! THE POINT NOEUD IS ENCOUNTERED FOR THE FIRST TIME
94  npoin_p(i)=npoin_p(i)+1
95 ! IS NOEUD A BOUNDARY POINT ?
96  IF(irand(noeud) .NE. 0) THEN
97  nptfr_p(i)= nptfr_p(i)+1
98  ENDIF
99 ! MODIFICATION OF KNOGL
100  knolg(npoin_p(i),i)=noeud
101  ENDIF
102  ENDDO
103  ENDDO
104 !
105  nptir_p(i)=0
106 !
107 ! NOMBRE DE NOEUD INTERFACE DU SDI
108 !
109  nbre_ef_i(i)=0 ! NOMBRE D'ELEMENTS FINIS INTERFACES DU SDI
110  DO j=1,nelem_p(i) ! ON PARCOURS A NOUVEAU LES ELEMENTS FINIS DU SDI
111  interfce=.false.
112  ef=elelg(j,i)
113  DO k=1,ndp_2d
114  noeud=ikles((ef-1)*3+k)
115  temp=hash_table_get(knogl, noeud, i)
116  IF(abs(nbre_ef_loc(temp)).NE.nbre_ef(noeud)) THEN
117  interfce=.true.
118  ENDIF
119  IF(nbre_ef_loc(temp).NE. nbre_ef(noeud).AND.
120  & nbre_ef_loc(temp).GT.0) THEN
121 ! NOEUD EST INTERFACE CAR IL RESTE DES ELEMENTS FINIS
122 ! HORS DE SDI QUI LE CONTIENT
123  interfce=.true.
124  nptir_p(i)=nptir_p(i)+1
125  CALL hash_table_insert(cut_p, nptir_p(i), i, noeud)
126  part_p(noeud,0)=part_p(noeud,0)+1
127  posi=part_p(noeud,0)
128  IF(posi.GT.nbmaxnshare-1) THEN
129  WRITE(lu,*) 'ERROR : AN INTERFACE NODE BELONGS TO
130  & MORE THAN NBMAXNSHARE-1 SUBDOMAINS'
131  CALL plante(1)
132  stop
133  ENDIF
134  part_p(noeud,posi)=i
135  nbre_ef_loc(temp)=-nbre_ef_loc(temp)
136  ENDIF
137  ENDDO
138  IF(interfce) THEN
139  nbre_ef_i(i)=nbre_ef_i(i)+1 ! L'ELEMENT FINI EST DONC AUSSI INTERFACE
140  ef_i(i, nbre_ef_i(i))=ef
141  ef_ii(i, nbre_ef_i(i))=j
142  ENDIF
143  ENDDO
144  ENDDO
145  END SUBROUTINE
subroutine compute_boundary_and_interface(NPARTS, NDP_2D, NPOIN_P, NPTFR_P, ELELG, NELEM_P, IKLES, KNOGL, CUT_P, EF_I, EF_II, NPTIR_P, NBRE_EF_I, KNOLG, IRAND, PART_P, NBRE_EF)
integer function hash_table_get(HT, X, Y)
recursive subroutine hash_table_insert(HT, X, Y, V)
Definition: bief.f:3