Salome HOME
Homard executable
[modules/homard.git] / src / tool / Creation_Maillage / cmalco.F
1       subroutine cmalco ( nomail,
2      >                    lgetco, taetco,
3      >                    ulsort, langue, codret )
4 c ______________________________________________________________________
5 c
6 c                             H O M A R D
7 c
8 c Outil de Maillage Adaptatif par Raffinement et Deraffinement d'EDF R&D
9 c
10 c Version originale enregistree le 18 juin 1996 sous le numero 96036
11 c aupres des huissiers de justice Simart et Lavoir a Clamart
12 c Version 11.2 enregistree le 13 fevrier 2015 sous le numero 2015/014
13 c aupres des huissiers de justice
14 c Lavoir, Silinski & Cherqui-Abrahmi a Clamart
15 c
16 c    HOMARD est une marque deposee d'Electricite de France
17 c
18 c Copyright EDF 1996
19 c Copyright EDF 1998
20 c Copyright EDF 2002
21 c Copyright EDF 2020
22 c ______________________________________________________________________
23 c
24 c    Creation du Maillage - ALlocation pour la mise en COnformite
25 c    -           -          --                         --
26 c ______________________________________________________________________
27 c
28 c but : decompte les entites a creer lors du decoupage de mise en
29 c       conformite des faces et des volumes.
30 c ______________________________________________________________________
31 c .        .     .        .                                            .
32 c .  nom   . e/s . taille .           description                      .
33 c .____________________________________________________________________.
34 c . nomail . e   .  ch8   . nom de l'objet contenant le maillage       .
35 c . lgetco . e   .   1    . longueur du tableau de l'etat courant      .
36 c . taetco . e   . lgetco . tableau de l'etat courant                  .
37 c . ulsort . e   .   1    . numero d'unite logique de la liste standard.
38 c . langue . e   .   1    . langue des messages                        .
39 c .        .     .        . 1 : francais, 2 : anglais                  .
40 c . codret . e/s .   1    . code de retour des modules                 .
41 c .        .     .        . 0 : pas de probleme                        .
42 c ______________________________________________________________________
43 c
44 c====
45 c 0. declarations et dimensionnement
46 c====
47 c
48 c 0.1. ==> generalites
49 c
50       implicit none
51       save
52 c
53       character*6 nompro
54       parameter ( nompro = 'CMALCO' )
55 c
56 #include "nblang.h"
57 c
58 c 0.2. ==> communs
59 c
60 #include "envex1.h"
61 c
62 #include "impr02.h"
63 c
64 #include "envca1.h"
65 #include "nombhe.h"
66 #include "nombpe.h"
67 #include "nouvnb.h"
68 c
69 c 0.3. ==> arguments
70 c
71       character*8 nomail
72 c
73       integer lgetco
74       integer taetco(lgetco)
75 c
76       integer ulsort, langue, codret
77 c
78 c 0.4. ==> variables locales
79 c
80       integer codava
81       integer nretap, nrsset
82       integer iaux, jaux
83 c
84       integer codre0
85       integer adtes2
86       integer adhes2
87       integer adpes2
88       integer adpys2
89 c
90       character*6 saux
91       character*8 norenu
92       character*8 nhnoeu, nhmapo, nharet, nhtria, nhquad
93       character*8 nhtetr, nhhexa, nhpyra, nhpent
94       character*8 nhelig
95       character*8 nhvois, nhsupe, nhsups
96       character*8 ndecfa
97 c
98       logical extrus
99 c
100       integer nbmess
101       parameter ( nbmess = 10 )
102       character*80 texte(nblang,nbmess)
103 c
104 c 0.5. ==> initialisations
105 c ______________________________________________________________________
106 c
107 c====
108 c 1. messages
109 c====
110 c
111       codava = codret
112 c
113 c=======================================================================
114       if ( codava.eq.0 ) then
115 c=======================================================================
116 c
117 c 1.3. ==> les messages
118 c
119 #include "impr01.h"
120 c
121 #ifdef _DEBUG_HOMARD_
122       write (ulsort,texte(langue,1)) 'Entree', nompro
123       call dmflsh (iaux)
124 #endif
125 c
126       texte(1,4) =
127      > '(/,a6,'' ALLOCATION MEMOIRE POUR LA CONFORMITE'')'
128       texte(1,5) = '(44(''=''),/)'
129       texte(1,6) = '(''Modification de taille des tableaux des '',a)'
130       texte(1,7) = '(5x,''==> code de retour :'',i8)'
131 c
132       texte(2,4) =
133      > '(/,a6,'' MEMORY ALLOCATION FOR CONFORMITY'')'
134       texte(2,5) = '(39(''=''),/)'
135       texte(2,6) = '(''Size modification of arrays for '',a)'
136       texte(2,7) = '(5x,''==> error code :'',i8)'
137 c
138 #include "impr03.h"
139 c
140 c 1.4. ==> le numero de sous-etape
141 c
142       nretap = taetco(1)
143       nrsset = taetco(2) + 1
144       taetco(2) = nrsset
145 c
146       call utcvne ( nretap, nrsset, saux, iaux, codret )
147 c
148 c 1.5. ==> le titre
149 c
150       write ( ulsort,texte(langue,4)) saux
151       write ( ulsort,texte(langue,5))
152 c
153 c====
154 c 2. recuperation des pointeurs
155 c====
156 c
157       if ( codret.eq.0 ) then
158 c
159 #ifdef _DEBUG_HOMARD_
160       write (ulsort,texte(langue,3)) 'UTNOMH', nompro
161 #endif
162 c
163       call utnomh ( nomail,
164      >                sdim,   mdim,
165      >               degre, maconf, homolo, hierar,
166      >              rafdef, nbmane, typcca, typsfr, maextr,
167      >              mailet,
168      >              norenu,
169      >              nhnoeu, nhmapo, nharet,
170      >              nhtria, nhquad,
171      >              nhtetr, nhhexa, nhpyra, nhpent,
172      >              nhelig,
173      >              nhvois, nhsupe, nhsups,
174      >              ulsort, langue, codret)
175 c
176       endif
177 c
178 c====
179 c 3. Reallocation des tableaux avec les nouvelles dimensions
180 c====
181 #ifdef _DEBUG_HOMARD_
182       write (ulsort,90002) '3. reallocation ; codret', codret
183 #endif
184 c
185       if ( codret.eq.0 ) then
186 c
187       iaux = 2
188       if ( typcca.eq.26 .or .typcca.eq.46 ) then
189         extrus = .false.
190       elseif ( maextr.ne.0 ) then
191         extrus = .true.
192       else
193         extrus = .false.
194       endif
195       jaux = 0
196 #ifdef _DEBUG_HOMARD_
197       write (ulsort,texte(langue,3)) 'CMAL01', nompro
198 #endif
199       call cmal01 (   iaux, extrus,
200      >              nomail, ndecfa,
201      >              permno, nouvno,
202      >              permar, nouvar,
203      >              permtr, nouvtr,
204      >              permqu, nouvqu,
205      >              permte, nouvte, jaux, provta,
206      >              permhe, nouvhe, jaux, provha,
207      >              permpe, nouvpe, jaux, provpa,
208      >              permpy, nouvpy, jaux, provya,
209      >              ulsort, langue, codret )
210 c
211       endif
212 cgn      call gmprsx(nompro,nomail//'.Volume.HOM_Py05')
213 cgn      call gmprsx(nompro,nomail//'.Volume.HOM_Py05.ConnDesc')
214 cgn      call gmprsx(nompro,nomail//'.Volume.HOM_Py05.ConnAret')
215 cgn      call gmprsx(nompro,nomail//'.Volume.HOM_Py05.InfoSupp')
216 c
217 c 3.2. ==> Les tetraedres
218 c
219 #ifdef _DEBUG_HOMARD_
220       write (ulsort,texte(langue,6)) mess14(langue,3,3)//' - avant'
221       write (ulsort,texte(langue,7)) codret
222       write (ulsort,90002) 'permte', permte
223       write (ulsort,90002) 'nouvte', nouvte
224 #endif
225 c
226       if ( permte.ne.nouvte ) then
227 c
228         if ( nbpeco.ne.0 .or. nbheco.ne.0 ) then
229 c
230           iaux = nbheco + nbpeco
231           call gmaloj ( nhtetr//'.InfoSup2', ' ',
232      >                  iaux  , adtes2, codre0 )
233 c
234           codret = max ( abs(codre0), codret )
235 c
236         endif
237 c
238 #ifdef _DEBUG_HOMARD_
239       write (ulsort,texte(langue,6)) mess14(langue,3,3)//' - apres'
240       write (ulsort,texte(langue,7)) codret
241 #endif
242 c
243       endif
244 c
245 c 3.3. ==> Les pyramides
246 c
247 #ifdef _DEBUG_HOMARD_
248       write (ulsort,texte(langue,6)) mess14(langue,3,5)//' - avant'
249       write (ulsort,texte(langue,7)) codret
250       write (ulsort,90002) 'permpy', permpy
251       write (ulsort,90002) 'nouvpy', nouvpy
252 #endif
253 c
254       if ( permpy.ne.nouvpy ) then
255 c
256         if ( nbpeco.ne.0 .or. nbheco.ne.0 ) then
257 c
258           iaux = nbheco + nbpeco
259           call gmaloj ( nhpyra//'.InfoSup2', ' ',
260      >                  iaux  , adpys2, codre0 )
261 c
262           codret = max ( abs(codre0), codret )
263 c
264         endif
265 c
266 #ifdef _DEBUG_HOMARD_
267       write (ulsort,texte(langue,6)) mess14(langue,3,5)//' - apres'
268       write (ulsort,texte(langue,7)) codret
269 #endif
270 c
271       endif
272 c
273 c 3.4. ==> Les hexaedres : filiation en tetraedres/pyramides
274 #ifdef _DEBUG_HOMARD_
275       write (ulsort,90002) '3.4. hexaedres ; codret', codret
276 #endif
277 c
278       if ( nbheco.ne.0 ) then
279 c
280         if ( codret.eq.0 ) then
281 c
282         iaux = nbheco*2
283         call gmaloj ( nhhexa//'.InfoSup2', ' ', iaux  , adhes2, codre0 )
284 c
285         codret = max ( abs(codre0), codret )
286 c
287         endif
288 c
289       endif
290 c
291 c 3.5. ==> Les pentaedres : filiation en tetraedres/pyramides
292 #ifdef _DEBUG_HOMARD_
293       write (ulsort,90002) '3.5. pentaedres ; codret', codret
294 #endif
295 c
296       if ( nbpeco.ne.0 ) then
297 c
298         if ( codret.eq.0 ) then
299 c
300         iaux = nbpeco*2
301         call gmaloj ( nhpent//'.InfoSup2', ' ', iaux  , adpes2, codre0 )
302 c
303         codret = max ( abs(codre0), codret )
304 c
305         endif
306 c
307       endif
308 c
309 c====
310 c 4. la fin
311 c====
312 c
313       if ( codret.ne.0 ) then
314 c
315 #include "envex2.h"
316 c
317       write (ulsort,texte(langue,1)) 'Sortie', nompro
318       write (ulsort,texte(langue,2)) codret
319 c
320       endif
321 c
322 #ifdef _DEBUG_HOMARD_
323       write (ulsort,texte(langue,1)) 'Sortie', nompro
324       call dmflsh (iaux)
325 #endif
326 c
327 c=======================================================================
328       endif
329 c=======================================================================
330 c
331       end