Salome HOME
Homard executable
[modules/homard.git] / src / tool / ES_HOMARD / esemh1.F
1       subroutine esemh1 ( nomail, nomfic, lnomfi,
2      >                    optecr,
3      >                    nhnoeu, nhmapo, nharet, nhtria, nhquad,
4      >                    nhtetr, nhhexa, nhpyra, nhpent,
5      >                    nhelig,
6      >                    nhsups,
7      >                    suifro, nocdfr,
8      >                    ulsort, langue, codret)
9 c
10 c ______________________________________________________________________
11 c
12 c                             H O M A R D
13 c
14 c Outil de Maillage Adaptatif par Raffinement et Deraffinement d'EDF R&D
15 c
16 c Version originale enregistree le 18 juin 1996 sous le numero 96036
17 c aupres des huissiers de justice Simart et Lavoir a Clamart
18 c Version 11.2 enregistree le 13 fevrier 2015 sous le numero 2015/014
19 c aupres des huissiers de justice
20 c Lavoir, Silinski & Cherqui-Abrahmi a Clamart
21 c
22 c    HOMARD est une marque deposee d'Electricite de France
23 c
24 c Copyright EDF 1996
25 c Copyright EDF 1998
26 c Copyright EDF 2002
27 c Copyright EDF 2020
28 c ______________________________________________________________________
29 c
30 c  Entree-Sortie : Ecriture du Maillage Homard - 1
31 c  -      -        -           -        -        -
32 c ______________________________________________________________________
33 c .  nom   . e/s . taille .           description                      .
34 c .____________________________________________________________________.
35 c . nomail . e   . char*8 . nom du maillage a ecrire                   .
36 c . nomfic . e   .char*(*). nom du fichier                             .
37 c . lnomfi . e   .   1    . longueur du nom du fichier                 .
38 c . optecr . e   .   1    . option d'ecriture                          .
39 c .        .     .        . >0 : on ecrit la frontiere discrete        .
40 c .        .     .        . <0 : on n'ecrit pas la frontiere discrete  .
41 c . nhsups . e   . char*8 . informations supplementaires caracteres 8  .
42 c . suifro . e   .   1    . 1 : pas de suivi de frontiere              .
43 c .        .     .        . 2x : frontiere discrete                    .
44 c .        .     .        . 3x : frontiere analytique                  .
45 c .        .     .        . 5x : frontiere cao                         .
46 c . nocdfr . e   . char8  . nom de l'objet description de la frontiere .
47 c . ulsort . e   .   1    . numero d'unite logique de la liste standard.
48 c . langue . e   .    1   . langue des messages                        .
49 c .        .     .        . 1 : francais, 2 : anglais                  .
50 c . codret . es  .    1   . code de retour des modules                 .
51 c .        .     .        . 0 : pas de probleme                        .
52 c ______________________________________________________________________
53 c
54 c====
55 c 0. declarations et dimensionnement
56 c====
57 c
58 c 0.1. ==> generalites
59 c
60       implicit none
61       save
62 c
63       character*6 nompro
64       parameter ( nompro = 'ESEMH1' )
65 c
66 #include "nblang.h"
67 #include "consts.h"
68 c
69 c 0.2. ==> communs
70 c
71 #include "gmenti.h"
72 #include "gmreel.h"
73 #include "gmstri.h"
74 c
75 #include "dicfen.h"
76 #include "envex1.h"
77 #include "envca1.h"
78 #include "nbutil.h"
79 #include "nombmp.h"
80 #include "nombar.h"
81 #include "nombtr.h"
82 #include "nombqu.h"
83 #include "nombno.h"
84 #include "nombte.h"
85 #include "nombpy.h"
86 #include "nombhe.h"
87 #include "nombpe.h"
88 c
89 c 0.3. ==> arguments
90 c
91       integer lnomfi
92       integer optecr
93       integer suifro
94 c
95       character*8 nomail, nhsups
96       character*(*) nomfic
97 c
98       character*8 nhnoeu, nhmapo, nharet, nhtria, nhquad
99       character*8 nhtetr, nhhexa, nhpyra, nhpent, nhelig
100       character*8 nocdfr
101 c
102       integer ulsort, langue, codret
103 c
104 c 0.4. ==> variables locales
105 c
106 #include "meddc0.h"
107 c
108       integer iaux, jaux, kaux
109       integer codre0
110       integer codre1, codre2, codre3
111       integer*8 idfmed
112       integer ltrav1, ltrav2
113       integer ptrav1, ptrav2
114       integer dimcst, lgnoig, nbnoco
115       integer adcocs
116       integer infmgl(0:30)
117       integer nbpqt
118       integer adinss
119       integer numdt, numit
120       integer sfnbso
121 c
122       character*8 ntrav1, ntrav2
123       character*64 nomamd
124       character*80 saux80
125       character*200 sau200
126 c
127       double precision instan
128 c
129       integer nbmess
130       parameter ( nbmess = 150 )
131       character*80 texte(nblang,nbmess)
132 c ______________________________________________________________________
133 c
134 c====
135 c 1. initialisations
136 c====
137 c
138 #include "impr01.h"
139 c
140 #ifdef _DEBUG_HOMARD_
141       write (ulsort,texte(langue,1)) 'Entree', nompro
142       call dmflsh (iaux)
143 #endif
144 c
145       texte(1,4) = '(''Ecriture complete.'')'
146       texte(1,5) = '(''Ecriture sans les frontieres.'')'
147 c
148       texte(2,4) = '(''Full writings.'')'
149       texte(2,5) = '(''Writings without any boundary.'')'
150 c
151 #include "impr03.h"
152 c
153 #ifdef _DEBUG_HOMARD_
154       if ( optecr.gt.0 ) then
155         iaux = 4
156       else
157         iaux = 5
158       endif
159       write (ulsort,texte(langue,iaux))
160 #endif
161 c
162 #include "esimpr.h"
163 c
164 c 1.2. ==> tableaux de travail
165 c
166       jaux = 0
167       do 12 , iaux = 1 , 10
168         call gmliat ( nhsups, iaux, kaux, codre0 )
169         if ( codre0.eq.0 ) then
170           jaux = max(jaux,kaux)
171         else
172           codret = codre0
173         endif
174    12 continue
175 c
176       if ( codret.eq.0 ) then
177 c
178       if ( mod(suifro,2).eq.0 ) then
179         call gmliat ( nocdfr, 3, sfnbso, codret )
180       else
181         sfnbso = 0
182         codre2 = 0
183       endif
184 c
185       endif
186 c
187 #ifdef _DEBUG_HOMARD_
188       write (ulsort,90002) 'Nombre elements ignores', nbelig
189       write (ulsort,90002) 'Noeuds de la frontiere ', sfnbso
190 #endif
191 c
192       if ( codret.eq.0 ) then
193 c
194       ltrav1 = max ( 4*nbnoto,
195      >             nbmpto, 5*nbarto, 5*nbtrto, 6*nbteto, 5*nbquto,
196      >             7*nbpyto, 8*nbheto, 5*nbpeto, 14*nbelig+1,
197      >             sfnbso )
198 #ifdef _DEBUG_HOMARD_
199       write (ulsort,90002) '==> ltrav1', ltrav1
200 #endif
201       call gmalot ( ntrav1, 'entier  ', ltrav1   , ptrav1, codre1 )
202 c
203 c   A TRAITER pas clair le +11 ...
204       ltrav2 = 25*( max ( nctfno, nctfmp, nctfar, nctftr, nctfqu,
205      >                    nctfte, nctfpy, nctfhe, nctfpe, 40 ) + 11 )
206       ltrav2 = max ( ltrav2, jaux+11 )
207       call gmalot ( ntrav2, 'chaine  ', ltrav2   , ptrav2, codre2 )
208 c
209       codre0 = min ( codre1, codre2 )
210       codret = max ( abs(codre0), codret,
211      >               codre1, codre2 )
212 c
213       endif
214 c
215 c 1.2. ==> Instants d'enregistrement du maillage
216 c
217       if ( codret.eq.0 ) then
218 c
219       numdt = ednodt
220       numit = ednoit
221       instan = edundt
222 c
223 #ifdef _DEBUG_HOMARD_
224       write (ulsort,90003) 'fichier', nomfic(1:lnomfi)
225       write (ulsort,90003) 'nomail',nomail
226       write (ulsort,90002) 'numdt ',numdt
227       write (ulsort,90002) 'numit ',numit
228       write (ulsort,90004) 'dt    ',instan
229 #endif
230 c
231       endif
232 c
233 c====
234 c 2. ouverture en mode d'ecrasement
235 c====
236 #ifdef _DEBUG_HOMARD_
237       write (ulsort,90002) '2. ouverture ; codret', codret
238 #endif
239 c
240       if ( codret.eq.0 ) then
241 c
242 #ifdef _DEBUG_HOMARD_
243       write (ulsort,texte(langue,3)) 'MFIOPE', nompro
244 #endif
245       call mfiope ( idfmed, nomfic(1:lnomfi), edcrea, codret )
246       if ( codret.ne.0 ) then
247         write (ulsort,texte(langue,9))
248       endif
249 c
250       endif
251 c
252 c====
253 c 3. description du fichier
254 c====
255 #ifdef _DEBUG_HOMARD_
256       write (ulsort,90002) '3. description fichier ; codret', codret
257 #endif
258 c
259       if ( codret.eq.0 ) then
260 c
261       saux80 = blan80
262       saux80(1:54) =
263      > 'Maillage au format HOMARD avec gestion des historiques'
264 c       123456789012345678901234567890123456789012345678901234
265 c       12345678901234567890
266 #ifdef _DEBUG_HOMARD_
267       write (ulsort,texte(langue,3)) 'ESDESC', nompro
268 #endif
269       call esdesc ( idfmed, saux80, sau200,
270      >              ulsort, langue, codret )
271 c
272       endif
273 c
274 c====
275 c 4. creation du maillage
276 c====
277 #ifdef _DEBUG_HOMARD_
278       write (ulsort,90002) '4. creation maillage ; codret', codret
279       write (ulsort,90002) 'sdim', sdim
280       write (ulsort,90002) 'mdim', mdim
281 #endif
282 c
283       if ( codret.eq.0 ) then
284 c
285       call gmadoj ( nhsups//'.Tab3', adinss, iaux, codre1 )
286       call gmliat ( nhsups, 1, iaux, codre2 )
287       nbpqt = iaux - 1
288 c
289       codre0 = min ( codre1, codre2 )
290       codret = max ( abs(codre0), codret,
291      >               codre1, codre2 )
292 c
293       endif
294 c
295       if ( codret.eq.0 ) then
296 c
297       nomamd = blan64
298       nomamd(1:8) = nomail
299 c
300 #ifdef _DEBUG_HOMARD_
301       write (ulsort,texte(langue,3)) 'ESEMM0', nompro
302 #endif
303       call esemm0 ( idfmed, nomamd,
304      >                sdim,   mdim, sau200,
305      >               nbpqt, smem(adinss),
306      >              ulsort, langue, codret)
307 c
308       if ( codret.ne.0 ) then
309         write(ulsort,texte(langue,78)) 'ESEMM0', codret
310       endif
311 c
312       endif
313 c
314 c====
315 c 5. Ecriture des noeuds
316 c====
317 #ifdef _DEBUG_HOMARD_
318       write (ulsort,90002) '5. Ecriture des noeuds ; codret', codret
319 #endif
320 c
321       if ( codret.eq.0 ) then
322 c
323 #ifdef _DEBUG_HOMARD_
324       write (ulsort,texte(langue,3)) 'ESECNO', nompro
325 #endif
326       call esecno ( idfmed, nomamd,
327      >              nhnoeu,
328      >              numdt, numit, instan,
329      >              ltrav1, imem(ptrav1),
330      >              ulsort, langue, codret)
331 c
332       endif
333 c
334 c====
335 c 6. Ecriture des entites mailles
336 c====
337 #ifdef _DEBUG_HOMARD_
338       write (ulsort,90002) '6. Ecriture des mailles ; codret', codret
339 #endif
340 c
341       if ( codret.eq.0 ) then
342 c
343 #ifdef _DEBUG_HOMARD_
344       write (ulsort,texte(langue,3)) 'ESECEN', nompro
345 #endif
346       call esecen ( idfmed, nomamd,
347      >              nhmapo, nharet, nhtria, nhquad,
348      >              nhtetr, nhhexa, nhpyra, nhpent,
349      >              numdt, numit, instan,
350      >              ltrav1, imem(ptrav1),
351      >              ulsort, langue, codret )
352 c
353       endif
354 c
355 c====
356 c 7. Ecriture des familles
357 c====
358 #ifdef _DEBUG_HOMARD_
359       write (ulsort,90002) '7. Ecriture des familles ; codret', codret
360 #endif
361 c
362       if ( codret.eq.0 ) then
363 c
364 #ifdef _DEBUG_HOMARD_
365       write (ulsort,texte(langue,3)) 'ESEMH2', nompro
366 #endif
367       call esemh2 ( idfmed, nomamd,
368      >              nhnoeu, nhmapo, nharet, nhtria, nhquad,
369      >              nhtetr, nhhexa, nhpyra, nhpent,
370      >              nhsups,
371      >              ltrav1, imem(ptrav1), ltrav2, smem(ptrav2),
372      >              ulsort, langue, codret)
373 c
374       endif
375 c
376 c====
377 c 8. Ecriture des informations supplementaires
378 c====
379 #ifdef _DEBUG_HOMARD_
380       write (ulsort,90002) '8. Informations supp ; codret', codret
381 #endif
382 c 8.1. ==> informations globales au maillage
383 c
384       if ( codret.eq.0 ) then
385 c
386       call gmliat ( nhnoeu, 2, dimcst, codre1 )
387       call gmliat ( nhnoeu, 3, lgnoig, codre2 )
388       call gmliat ( nhnoeu, 4, nbnoco, codre3)
389 c
390       codre0 = min ( codre1, codre2, codre3 )
391       codret = max ( abs(codre0), codret,
392      >               codre1, codre2, codre3 )
393 c
394       endif
395 c
396       if ( codret.eq.0 ) then
397 c
398 c envca1 + divers
399       infmgl( 1) = sdim
400       infmgl( 2) = mdim
401       infmgl( 3) = degre
402       infmgl( 4) = maconf
403       infmgl( 5) = homolo
404       infmgl( 6) = hierar
405       infmgl( 7) = rafdef
406       infmgl( 8) = nbmane
407       infmgl( 9) = typcca
408       infmgl(10) = typsfr
409       infmgl(11) = maextr
410       infmgl(12) = mailet
411       infmgl(13) = dimcst
412       infmgl(14) = lgnoig
413       infmgl(15) = nbnoco
414 c nbutil
415       infmgl(16) = sdimca
416       infmgl(17) = mdimca
417 c
418       infmgl(0) = 17
419 c
420       endif
421 c
422 c 8.2. ==> Une coordonnee constante ?
423 c
424       if ( codret.eq.0 ) then
425 c
426       if ( dimcst.gt.0 ) then
427 c
428         call gmadoj ( nhnoeu//'.CoorCons', adcocs, iaux, codre0 )
429 c
430         codret = max ( abs(codre0), codret )
431 c
432       endif
433 c
434       endif
435 c
436 c 8.3 ==> ecriture
437 c
438       if ( codret.eq.0 ) then
439 c
440 #ifdef _DEBUG_HOMARD_
441       write (ulsort,texte(langue,3)) 'ESECSU', nompro
442 #endif
443       call esecsu ( idfmed,
444      >              nomail,
445      >              nhnoeu,
446      >              nhmapo, nharet, nhtria, nhquad,
447      >              nhtetr, nhhexa, nhpyra, nhpent,
448      >              infmgl,
449      >              dimcst, rmem(adcocs),
450      >              numdt, numit, instan,
451      >              ulsort, langue, codret )
452 c
453       endif
454 c
455 c====
456 c 9. Ecriture des eventuels elements ignores
457 c====
458 #ifdef _DEBUG_HOMARD_
459       write (ulsort,90002) '9. Elements ignores ; codret', codret
460 #endif
461 c
462       if ( nbelig.ne.0 ) then
463 c
464         if ( codret.eq.0 ) then
465 c
466 #ifdef _DEBUG_HOMARD_
467       write (ulsort,texte(langue,3)) 'ESECIG', nompro
468 #endif
469         call esecig ( idfmed,
470      >                nhelig,
471      >                imem(ptrav1),
472      >                ulsort, langue, codret )
473 c
474         endif
475 c
476       endif
477 c
478 c====
479 c 10. Ecriture de l'eventuelle frontiere discrete
480 c====
481 #ifdef _DEBUG_HOMARD_
482       write (ulsort,90002) '10. Frontiere discrete ; codret', codret
483 #endif
484 c
485       if ( mod(suifro,2).eq.0 .and. optecr.gt.0 ) then
486 c
487         if ( codret.eq.0 ) then
488 c
489 #ifdef _DEBUG_HOMARD_
490       write (ulsort,texte(langue,3)) 'ESECFD', nompro
491 #endif
492         call esecfd ( idfmed,
493      >                nocdfr,
494      >                ltrav1, imem(ptrav1), ltrav2, smem(ptrav2),
495      >                ulsort, langue, codret )
496 c
497         endif
498 c
499       endif
500 c
501 c====
502 c 11. fermeture du fichier
503 c====
504 c
505 #ifdef _DEBUG_HOMARD_
506       write (ulsort,90002) '11. fermeture du fichier ; codret', codret
507 #endif
508 c
509       if ( codret.eq.0 ) then
510 c
511 #ifdef _DEBUG_HOMARD_
512       write (ulsort,texte(langue,3)) 'MFICLO', nompro
513 #endif
514       call mficlo ( idfmed, codret )
515       if ( codret.ne.0 ) then
516         write (ulsort,texte(langue,10))
517       endif
518 c
519       endif
520 c
521 c====
522 c 12. menage
523 c====
524 #ifdef _DEBUG_HOMARD_
525       write (ulsort,90002) '12. menage ; codret', codret
526 #endif
527 c
528       if ( codret.eq.0 ) then
529 c
530       call gmlboj ( ntrav1 , codre1 )
531       call gmlboj ( ntrav2 , codre2 )
532 c
533       codre0 = min ( codre1, codre2 )
534       codret = max ( abs(codre0), codret,
535      >               codre1, codre2 )
536 c
537       endif
538 c
539 c====
540 c 13. la fin
541 c====
542 c
543       if ( codret.ne.0 ) then
544 c
545 #include "envex2.h"
546 c
547       write (ulsort,texte(langue,1)) 'Sortie', nompro
548       write (ulsort,texte(langue,2)) codret
549 c
550       endif
551 c
552 #ifdef _DEBUG_HOMARD_
553       write (ulsort,texte(langue,1)) 'Sortie', nompro
554       call dmflsh (iaux)
555 #endif
556 c
557       end