Salome HOME
Homard executable
[modules/homard.git] / src / tool / Utilitaire / utmoch.F
1       subroutine utmoch ( nocham, option,
2      >                    nomobj, npfonc,
3      >                    nbcomp, nbtvch, typcha,
4      >                    adnocp, adcaen, adcare, adcaca,
5      >                    ulsort, langue, codret )
6 c ______________________________________________________________________
7 c
8 c                             H O M A R D
9 c
10 c Outil de Maillage Adaptatif par Raffinement et Deraffinement d'EDF R&D
11 c
12 c Version originale enregistree le 18 juin 1996 sous le numero 96036
13 c aupres des huissiers de justice Simart et Lavoir a Clamart
14 c Version 11.2 enregistree le 13 fevrier 2015 sous le numero 2015/014
15 c aupres des huissiers de justice
16 c Lavoir, Silinski & Cherqui-Abrahmi a Clamart
17 c
18 c    HOMARD est une marque deposee d'Electricite de France
19 c
20 c Copyright EDF 1996
21 c Copyright EDF 1998
22 c Copyright EDF 2002
23 c Copyright EDF 2020
24 c ______________________________________________________________________
25 c
26 c    UTilitaire - MOdification d'un CHamp
27 c    --           --                --
28 c ______________________________________________________________________
29 c .        .     .        .                                            .
30 c .  nom   . e/s . taille .           description                      .
31 c .____________________________________________________________________.
32 c . nocham . e   . char8  . nom de l'objet champ                       .
33 c . option . e   .    1   . option de la modification :                .
34 c .        .     .        . 1 : ajout de la fonction nomobj            .
35 c . nomobj . e   . char8  . nom de la fonction a ajouter               .
36 c . npfonc . e   . char8  . nom de la fonction associee                .
37 c . nbcomp .   s .   1    . nombre de composantes                      .
38 c . nbtvch .   s .   1    . nombre de tableaux du champ                .
39 c . typcha .   s .   1    . edin64/edfl64 selon entier/reel            .
40 c . adnocp .   s .   1    . adresse des noms des champ et composantes  .
41 c . adcaen .   s .   1    . adresse des caracteristiques entieres      .
42 c . adcare .   s .   1    . adresse des caracteristiques reelles       .
43 c . adcaca .   s .   1    . adresse des caracteristiques caracteres    .
44 c . ulsort . e   .   1    . numero d'unite logique de la liste standard.
45 c . langue . e   .    1   . langue des messages                        .
46 c .        .     .        . 1 : francais, 2 : anglais                  .
47 c . codret . es  .    1   . code de retour des modules                 .
48 c .        .     .        . 0 : pas de probleme                        .
49 c .        .     .        . 1 : probleme                               .
50 c ______________________________________________________________________
51 c
52 c====
53 c 0. declarations et dimensionnement
54 c====
55 c
56 c 0.1. ==> generalites
57 c
58       implicit none
59       save
60 c
61       character*6 nompro
62       parameter ( nompro = 'UTMOCH' )
63 c
64 #include "nblang.h"
65 #include "esutil.h"
66 c
67 c 0.2. ==> communs
68 c
69 #include "envex1.h"
70 c
71 #include "gmstri.h"
72 #include "gmenti.h"
73 #include "gmreel.h"
74 c
75 c 0.3. ==> arguments
76 c
77       integer option
78       integer nbcomp, nbtvch, typcha
79       integer adnocp, adcaen, adcare, adcaca
80 c
81       character*8 nocham, nomobj, npfonc
82 c
83       integer ulsort, langue, codret
84 c
85 c 0.4. ==> variables locales
86 c
87       integer iaux, jaux, kaux
88       integer codre1, codre2, codre3, codre4
89       integer codre0
90 c
91       integer nbtach
92       integer typgeo, ngauss, nbenmx, nbvapr, nbtyas
93       integer carsup, nbtafo, typint
94       integer advale, advalr, adobch, adprpg, adtyas
95 c
96       character*64 nomcha
97 c
98       integer nbmess
99       parameter ( nbmess = 10 )
100       character*80 texte(nblang,nbmess)
101 c
102 c 0.5. ==> initialisations
103 c ______________________________________________________________________
104 c
105 c====
106 c 1. initialisations
107 c====
108 c
109 c 1.1. ==> messages
110 c
111 #include "impr01.h"
112 c
113 #ifdef _DEBUG_HOMARD_
114       write (ulsort,texte(langue,1)) 'Entree', nompro
115       call dmflsh (iaux)
116 #endif
117 c
118       texte(1,4) = '(''Champ avant modification :'')'
119       texte(1,5) = '(''Champ apres modification :'')'
120       texte(1,6) =
121      > '(''Nombre initial de tableaux du champ         :'',i5)'
122       texte(1,7) =
123      > '(''Nombre de tableaux de la fonction a ajouter :'',i5)'
124       texte(1,8) =
125      > '(''Nombre final de tableaux du champ           :'',i5)'
126 c
127       texte(2,4) = '(''Field before modification :'')'
128       texte(2,5) = '(''Field after modification :'')'
129       texte(2,6) =
130      > '(''Initial number of arrays in the field        :'',i5)'
131       texte(2,7) =
132      > '(''Number of arrays in the function to be added :'',i5)'
133       texte(2,8) =
134      > '(''Final number of arrays in the field          :'',i5)'
135 c
136 #ifdef _DEBUG_HOMARD_
137       write (ulsort,texte(langue,4))
138       call gmprsx (nompro, nocham )
139       call gmprsx (nompro, nocham//'.Nom_Comp' )
140       call gmprsx (nompro, nocham//'.Cham_Ent' )
141 cgn      call gmprsx (nompro, nocham//'.Cham_Ree' )
142 cgn      call gmprsx (nompro, nocham//'.Cham_Car' )
143 #endif
144 c
145 c====
146 c 2. caracteristiques de l'objet contenant le champ
147 c====
148 c
149 c 2.1. ==> nombre de tableaux de valeurs pour ce champ
150 c
151       if ( codret.eq.0 ) then
152 c
153 #ifdef _DEBUG_HOMARD_
154       write (ulsort,texte(langue,3)) 'UTCACH', nompro
155 #endif
156       call utcach ( nocham,
157      >              nomcha,
158      >              nbcomp, nbtvch, typcha,
159      >              adnocp, adcaen, adcare, adcaca,
160      >              ulsort, langue, codret )
161 c
162       endif
163 #ifdef _DEBUG_HOMARD_
164       write (ulsort,texte(langue,6)) nbtvch
165 #endif
166 c
167 c 2.2. ==> nombre de tableaux de valeurs pour ce champ et cette fonction
168 c
169       if ( codret.eq.0 ) then
170 c
171 cgn      write(ulsort,*) 'au depart'
172       nbtach = 0
173 c
174       do 21 , iaux = 1 , nbtvch
175 c
176         jaux = adcaca + nbincc*(iaux-1)
177 c
178         if ( smem(jaux).eq.npfonc ) then
179 c
180           nbtach = nbtach + 1
181 c
182         endif
183 cgn      call gmprot (nompro, nocham//'.Cham_Ent',
184 cgn     >             nbinec*(iaux-1)+1, nbinec*iaux )
185 c
186    21 continue
187 c
188 #ifdef _DEBUG_HOMARD_
189       write (ulsort,texte(langue,7)) nbtach
190 #endif
191       endif
192 c
193 c====
194 c 3. ajout d'une fonction
195 c====
196 c
197       if ( option.eq.1 ) then
198 c
199 c 3.1. ==> caracteristiques de la fonction
200 c
201       if ( codret.eq.0 ) then
202 c
203 cgn      call gmprsx (nompro, nomobj )
204 #ifdef _DEBUG_HOMARD_
205       write (ulsort,texte(langue,3)) 'UTCAFO', nompro
206 #endif
207       call utcafo ( nomobj,
208      >              typcha,
209      >              typgeo, ngauss, nbenmx, nbvapr, nbtyas,
210      >              carsup, nbtafo, typint,
211      >              advale, advalr, adobch, adprpg, adtyas,
212      >              ulsort, langue, codret )
213 c
214       endif
215 c
216 c 3.2. ==> allongement de la structure pour accueillir les nbtafo
217 c          tableaux de la fonction
218 c
219       if ( codret.eq.0 ) then
220 c
221       call gmecat ( nocham, 2, nbtvch+nbtach, codre1 )
222       iaux = nbinec*(nbtvch+nbtach)
223       call gmmod ( nocham//'.Cham_Ent',
224      >             adcaen, nbinec*nbtvch, iaux, 1, 1, codre2 )
225       iaux = nbtvch+nbtach
226       call gmmod ( nocham//'.Cham_Ree',
227      >             adcare, nbtvch, iaux, 1, 1, codre3 )
228       iaux = nbincc*(nbtvch+nbtach)
229       call gmmod ( nocham//'.Cham_Car',
230      >             adcaca, nbincc*nbtvch, iaux, 1, 1, codre4 )
231 c
232       codre0 = min ( codre1, codre2, codre3, codre4 )
233       codret = max ( abs(codre0), codret,
234      >               codre1, codre2, codre3, codre4 )
235 c
236       endif
237 cgn      write(ulsort,*) 'apres 32'
238 cgn      call gmprot (nompro, nocham//'.Cham_Ent',  1, nbinec )
239 cgn      call gmprot (nompro, nocham//'.Cham_Ent', nbinec+1, 2*nbinec )
240 cgn      call gmprsx (nompro, nocham//'.Cham_Ent' )
241 cgn      call gmprsx (nompro, nocham//'.Cham_Car' )
242 c
243 c 3.3. ==> transfert des caracteristiques de la fonction
244 c          Rappel :
245 c       1. type de support au sens MED
246 c       2. numero du pas de temps
247 c       3. numero d'ordre
248 c       4. nombre de points de Gauss
249 c       5. nombre d'entites support
250 c       6. nombre de valeurs du profil eventuel
251 c       7. supports associes
252 c       8. noeuds par elements/points de Gauss/autre
253 c       9. numero du 1er tableau dans la fonction
254 c       10. -1 ou champ elga/champ elno
255 c       11. type interpolation
256 c       21-nbinec. type des supports associes
257 c
258       if ( codret.eq.0 ) then
259 c
260       do 33 , iaux = 1 , nbtach
261 c
262         jaux = adcaen + nbinec*(nbtvch+iaux-1)
263         imem(jaux)   = typgeo
264         imem(jaux+3) = ngauss
265         imem(jaux+4) = nbenmx
266         imem(jaux+5) = nbvapr
267         imem(jaux+6) = nbtyas
268         imem(jaux+7) = carsup
269         if ( carsup.ne.2 ) then
270           imem(jaux+9) = 0
271         endif
272         imem(jaux+10) = typint
273         if ( nbtyas.gt.0 ) then
274           do 331 , kaux = 1 , nbtyas
275             imem(jaux+19+kaux) = imem(adtyas+kaux-1)
276   331     continue
277         endif
278 c
279         jaux = adcaca + nbincc*(nbtvch+iaux-1)
280         smem(jaux  ) = nomobj
281         smem(jaux+1) = smem(adprpg)
282         smem(jaux+2) = smem(adprpg+1)
283 c
284    33 continue
285 c
286       endif
287 cgn      write(ulsort,*) 'apres 33'
288 cgn      call gmprot (nompro, nocham//'.Cham_Ent',  1, nbinec )
289 cgn      call gmprot (nompro, nocham//'.Cham_Ent', nbinec+1, 2*nbinec )
290 cgn      call gmprsx (nompro, nocham//'.Cham_Ent' )
291 cgn      call gmprsx (nompro, nocham//'.Cham_Car' )
292 c
293 c 3.4. ==> transfert des caracteristiques temporelles du champ
294 c          on doit recopier celles de la fonction associee
295 c
296       if ( codret.eq.0 ) then
297 c
298 cgn      write(ulsort,*) 'apres 34'
299       kaux = 0
300 c
301       do 34 , iaux = 1 , nbtvch
302 c
303         jaux = adcaca + nbincc*(iaux-1)
304 c
305         if ( smem(jaux).eq.npfonc ) then
306 c
307 c         2. numero du pas de temps
308           imem(adcaen+nbinec*(nbtvch+kaux)+1) =
309      >    imem(adcaen+nbinec*(iaux-1)+1)
310 c         3. numero d'ordre
311           imem(adcaen+nbinec*(nbtvch+kaux)+2) =
312      >    imem(adcaen+nbinec*(iaux-1)+2)
313 c         9. numero du 1er tableau dans la fonction
314           imem(adcaen+nbinec*(nbtvch+kaux)+8) =
315      >    imem(adcaen+nbinec*(iaux-1)+8)
316 c
317           rmem(adcare+(nbtvch+kaux))     = rmem(adcare+iaux-1)
318 c
319           kaux = kaux + 1
320 cgn      call gmprot (nompro, nocham//'.Cham_Ent',
321 cgn     >             nbinec*(nbtvch+kaux-1)+1, nbinec*(nbtvch+kaux) )
322 c
323         endif
324 c
325    34 continue
326 c
327       endif
328 cgn      call gmprot (nompro, nocham//'.Cham_Ent',  1, nbinec )
329 cgn      call gmprot (nompro, nocham//'.Cham_Ent', nbinec+1, 2*nbinec )
330 cgn      call gmprsx (nompro, nocham//'.Cham_Ent' )
331 cgn      call gmprsx (nompro, nocham//'.Cham_Car' )
332 c
333 c 3.5. ==> cumul du nombre total de tableaux pour le champ
334 c
335       nbtvch = nbtvch + kaux
336 c
337 #ifdef _DEBUG_HOMARD_
338       write (ulsort,texte(langue,8)) nbtvch
339 #endif
340 c
341       endif
342 c
343 c====
344 c 4. la fin
345 c====
346 c
347 #ifdef _DEBUG_HOMARD_
348       write (ulsort,texte(langue,5))
349       call gmprsx (nompro, nocham )
350       call gmprsx (nompro, nocham//'.Nom_Comp' )
351       call gmprsx (nompro, nocham//'.Cham_Ent' )
352       call gmprsx (nompro, nocham//'.Cham_Ree' )
353       call gmprsx (nompro, nocham//'.Cham_Car' )
354 #endif
355 c
356       if ( codret.ne.0 ) then
357 c
358 #include "envex2.h"
359 c
360       write (ulsort,texte(langue,1)) 'Sortie', nompro
361       write (ulsort,texte(langue,2)) codret
362 c
363       endif
364 c
365 #ifdef _DEBUG_HOMARD_
366       write (ulsort,texte(langue,1)) 'Sortie', nompro
367       call dmflsh (iaux)
368 #endif
369 c
370       end