~ubuntu-branches/ubuntu/precise/code-saturne/precise

« back to all changes in this revision

Viewing changes to src/lagr/lagune.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
!-------------------------------------------------------------------------------
2
2
 
3
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
 
3
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
25
20
 
26
21
!-------------------------------------------------------------------------------
27
22
 
28
23
subroutine lagune &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
34
 
   nvar   , nscal  , nphas  ,                                     &
 
26
 ( lndnod ,                                                       &
 
27
   nvar   , nscal  ,                                              &
35
28
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
36
29
   ntersl , nvlsta , nvisbr ,                                     &
37
 
   nideve , nrdeve , nituse , nrtuse ,                            &
38
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
39
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
40
 
   icocel , itycel , ifrlag , itepa  , indep  , ibord  ,          &
41
 
   idevel , ituser , ia     ,                                     &
42
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
30
   icocel , itycel , ifrlag , itepa  ,                            &
 
31
   dlgeo  ,                                                       &
43
32
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
44
33
   coefa  , coefb  ,                                              &
45
 
   ettp   , ettpa  , tepa   , statis , stativ , tslagr , parbor , &
46
 
   taup   , tlag   , piil   , bx     , vagaus , tsuf   , tsup   , &
47
 
   tsvar  , tempct , tsfext , cpgd1  , cpgd2  , cpght  ,          &
48
 
   gradpr , gradvf , croule , brgaus , terbru ,                   &
49
 
   w1     , w2     , w3     , auxl   , auxl2  ,                   &
50
 
   rdevel , rtuser , ra     )
 
34
   ettp   , ettpa  , tepa   , statis , stativ , tslagr , parbor )
51
35
 
52
36
!===============================================================================
53
37
! FONCTION :
64
48
!__________________.____._____.________________________________________________.
65
49
! name             !type!mode ! role                                           !
66
50
!__________________!____!_____!________________________________________________!
67
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
68
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
69
 
! ndim             ! i  ! <-- ! spatial dimension                              !
70
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
71
 
! ncel             ! i  ! <-- ! number of cells                                !
72
 
! nfac             ! i  ! <-- ! number of interior faces                       !
73
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
74
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
75
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
76
 
! nnod             ! i  ! <-- ! number of vertices                             !
77
51
! lndnod           ! e  ! <-- ! dim. connectivite cellules->faces              !
78
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
79
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
80
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
81
52
! nvar             ! i  ! <-- ! total number of variables                      !
82
53
! nscal            ! i  ! <-- ! total number of scalars                        !
83
 
! nphas            ! i  ! <-- ! number of phases                               !
84
54
! nbpmax           ! e  ! <-- ! nombre max de particulies autorise             !
85
55
! nvp              ! e  ! <-- ! nombre de variables particulaires              !
86
56
! nvp1             ! e  ! <-- ! nvp sans position, vfluide, vpart              !
89
59
! ntersl           ! e  ! <-- ! nbr termes sources de couplage retour          !
90
60
! nvlsta           ! e  ! <-- ! nombre de var statistiques lagrangien          !
91
61
! nvisbr           ! e  ! <-- ! nombre de statistiques aux frontieres          !
92
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
93
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
94
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
95
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
96
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
97
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
98
 
! iprfml           ! te ! <-- ! proprietes d'une famille                       !
99
 
!  (nfml,nprfml    !    !     !                                                !
100
 
! ipnfac           ! te ! <-- ! position du premier noeud de chaque            !
101
 
!   (lndfac)       !    !     !  face interne dans nodfac                      !
102
 
! nodfac           ! te ! <-- ! connectivite faces internes/noeuds             !
103
 
!   (nfac+1)       !    !     !                                                !
104
 
! ipnfbr           ! te ! <-- ! position du premier noeud de chaque            !
105
 
!   (lndfbr)       !    !     !  face de bord dans nodfbr                      !
106
 
! nodfbr           ! te ! <-- ! connectivite faces de bord/noeuds              !
107
 
!   (nfabor+1)     !    !     !                                                !
108
62
! icocel           ! te ! --> ! connectivite cellules -> faces                 !
109
63
!   (lndnod)       !    !     !    face de bord si numero negatif              !
110
64
! itycel           ! te ! --> ! connectivite cellules -> faces                 !
113
67
!   (nfabor)       !    !     !  pour le module lagrangien                     !
114
68
! itepa            ! te ! --> ! info particulaires (entiers)                   !
115
69
! (nbpmax,nivep    !    !     !   (cellule de la particule,...)                !
116
 
! indep            ! te ! --> ! pour chaque particule :                        !
117
 
!   (nbpmax)       !    !     !   numero de la cellule de depart               !
118
 
! ibord            ! te ! --> ! contient le numero de la                       !
119
 
!   (nbpmax)       !    !     !   face d'interaction part/frontiere            !
120
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
121
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
122
 
! ia(*)            ! ia ! --- ! main integer work array                        !
123
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
124
 
!  (ndim, ncelet)  !    !     !                                                !
125
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
126
 
!  (ndim, nfac)    !    !     !                                                !
127
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
128
 
!  (ndim, nfabor)  !    !     !                                                !
129
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
130
 
!  (ndim, nfac)    !    !     !                                                !
131
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
132
 
!  (ndim, nfabor)  !    !     !                                                !
133
 
! xyznod           ! tr ! <-- ! coordonnes des noeuds                          !
134
 
! (ndim,nnod)      !    !     !                                                !
135
 
! volume(ncelet    ! tr ! <-- ! volume d'un des ncelet elements                !
 
70
! dlgeo            ! tr ! --> ! tableau contenant les donnees geometriques     !
 
71
! (nfabor,ngeol)   !    !     ! pour le sous-modele de depot                   !
136
72
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
137
73
! rtp, rtpa        ! tr ! <-- ! variables de calcul au centre des              !
138
74
! (ncelet,*)       !    !     !    cellules (instant courant et prec)          !
143
79
!  (nfabor, *)     !    !     !                                                !
144
80
! ettp             ! tr ! --> ! tableaux des variables liees                   !
145
81
!  (nbpmax,nvp)    !    !     !   aux particules etape courante                !
146
 
! ettpa            ! tr ! --> ! tableaux des variables liees                   !
 
82
! ettp             ! tr ! --> ! tableaux des variables liees                   !
147
83
!  (nbpmax,nvp)    !    !     !   aux particules etape precedente              !
148
84
! tepa             ! tr ! --> ! info particulaires (reels)                     !
149
85
! (nbpmax,nvep)    !    !     !   (poids statistiques,...)                     !
156
92
!(ncelet,ntersl    !    !     !   lagrangien sur la phase porteuse             !
157
93
! parbor           ! tr ! --> ! infos sur interaction des particules           !
158
94
!(nfabor,nvisbr    !    !     !   aux faces de bord                            !
159
 
! taup(nbpmax)     ! tr ! --> ! temps caracteristique dynamique                !
160
 
! tlag(nbpmax)     ! tr ! --> ! temps caracteristique fluide                   !
161
 
! piil(nbpmax,3    ! tr ! --> ! terme dans l'integration des eds up            !
162
 
! bx(nbpmax,3,2    ! tr ! --> ! caracteristiques de la turbulence              !
163
 
! vagaus           ! tr ! --> ! variables aleatoires gaussiennes               !
164
 
!(nbpmax,nvgaus    !    !     !                                                !
165
 
! tsup(nbpmax,3    ! tr ! --> ! prediction 1er sous-pas pour                   !
166
 
!                  !    !     !   la vitesse des particules                    !
167
 
! tsuf(nbpmax,3    ! tr ! --> ! prediction 1er sous-pas pour                   !
168
 
!                  !    !     !   la vitesse du fluide vu                      !
169
 
! tsvar            ! tr ! --> ! prediction 1er sous-pas pour la                !
170
 
! (nbpmax,nvp1)    !    !     !   variable courante, utilise pour la           !
171
 
! tempct           ! tr ! --> ! temps caracteristique thermique                !
172
 
! (nbpmax,2)       !    !     !                                                !
173
 
! tsfext(nbpmax    ! tr ! --> ! forces externes                                !
174
 
! cpgd1,cpgd2,     ! tr ! --> ! termes de devolatilisation 1 et 2 et           !
175
 
!  cpght(nbpmax    !    !     !   de combusion heterogene (charbon             !
176
 
!                  !    !     !   avec couplage retour thermique)              !
177
 
! gradpr(ncel,3    ! tr ! --> ! gradient de pression                           !
178
 
! gradvf(ncel,9    ! tr ! --> ! gradient de vitesse fluide                     !
179
 
! croule           ! tr ! --> ! fonction d'importance pour roulette            !
180
 
!   (ncelet)       !    !     !   russe                                        !
181
 
! w1..w3(ncelet    ! tr ! --- ! tableaux de travail                            !
182
 
! auxl(nbpmax,3    ! tr ! --- ! tableau de travail                             !
183
 
! auxl2            ! tr ! --- ! tableau de travail                             !
184
 
!    (nbpmax,7)    !    !     !                                                !
185
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
186
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
187
 
! ra(*)            ! ra ! --- ! main real work array                           !
188
95
!__________________!____!_____!________________________________________________!
189
96
 
190
97
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
191
98
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
192
99
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
193
100
!            --- tableau de travail
 
101
!===============================================================================
 
102
 
 
103
!===============================================================================
 
104
! Module files
 
105
!===============================================================================
 
106
 
 
107
use paramx
 
108
use numvar
 
109
use optcal
 
110
use entsor
 
111
use cstphy
 
112
use cstnum
 
113
use parall
 
114
use period
 
115
use pointe
 
116
use lagpar
 
117
use lagran
 
118
use mesh
 
119
use ppppar
 
120
use ppthch
 
121
use ppincl
194
122
 
195
123
!===============================================================================
196
124
 
197
125
implicit none
198
126
 
199
 
!===============================================================================
200
 
! Common blocks
201
 
!===============================================================================
202
 
 
203
 
include "paramx.h"
204
 
include "numvar.h"
205
 
include "optcal.h"
206
 
include "entsor.h"
207
 
include "cstphy.h"
208
 
include "cstnum.h"
209
 
include "pointe.h"
210
 
include "period.h"
211
 
include "parall.h"
212
 
include "lagpar.h"
213
 
include "lagran.h"
214
 
 
215
 
!===============================================================================
216
 
 
217
127
! Arguments
218
128
 
219
 
integer          idbia0 , idbra0
220
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
221
 
integer          nfml   , nprfml
222
 
integer          nnod   , lndnod , lndfac , lndfbr , ncelbr
223
 
integer          nvar   , nscal  , nphas
 
129
integer          lndnod
 
130
integer          nvar   , nscal
224
131
integer          nbpmax , nvp    , nvp1   , nvep  , nivep
225
132
integer          ntersl , nvlsta , nvisbr
226
 
integer          nideve , nrdeve , nituse , nrtuse
227
 
integer          ifacel(2,nfac) , ifabor(nfabor)
228
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
229
 
integer          iprfml(nfml,nprfml)
230
 
integer          ipnfac(nfac+1) , nodfac(lndfac)
231
 
integer          ipnfbr(nfabor+1) , nodfbr(lndfbr)
 
133
 
232
134
integer          icocel(lndnod) , itycel(ncelet+1)
233
135
integer          ifrlag(nfabor) , itepa(nbpmax,nivep)
234
 
integer          indep(nbpmax) , ibord(nbpmax)
235
 
integer          idevel(nideve) , ituser(nituse)
236
 
integer          ia(*)
237
136
 
238
 
double precision xyzcen(ndim,ncelet)
239
 
double precision surfac(ndim,nfac) , surfbo(ndim,nfabor)
240
 
double precision cdgfac(ndim,nfac) , cdgfbo(ndim,nfabor)
241
 
double precision xyznod(ndim,nnod) , volume(ncelet)
242
137
double precision dt(ncelet) , rtp(ncelet,*) , rtpa(ncelet,*)
243
138
double precision propce(ncelet,*)
244
139
double precision propfa(nfac,*) , propfb(nfabor,*)
245
140
double precision coefa(nfabor,*) , coefb(nfabor,*)
246
 
double precision ettp(nbpmax,nvp) , ettpa(nbpmax,nvp)
 
141
double precision ettp(nbpmax,nvp), ettpa(nbpmax,nvp)
247
142
double precision tepa(nbpmax,nvep)
248
143
double precision statis(ncelet,nvlsta)
249
144
double precision stativ(ncelet,nvlsta-1)
250
145
double precision tslagr(ncelet,ntersl)
251
146
double precision parbor(nfabor,nvisbr)
252
 
double precision taup(nbpmax) , tlag(nbpmax,3) , piil(nbpmax,3)
253
 
double precision vagaus(nbpmax,*) , bx(nbpmax,3,2)
254
 
double precision tsuf(nbpmax,3) , tsup(nbpmax,3)
255
 
double precision tsvar(nbpmax,nvp1)
256
 
double precision tempct(nbpmax,2) , tsfext(nbpmax)
257
 
double precision cpgd1(nbpmax) , cpgd2(nbpmax) , cpght(nbpmax)
258
 
double precision brgaus(nbpmax,*) , terbru(nbpmax)
259
 
double precision gradpr(ncelet,3) , gradvf(ncelet,9)
260
 
double precision croule(ncelet)
261
 
double precision w1(ncelet) ,  w2(ncelet) ,  w3(ncelet)
262
 
double precision auxl(nbpmax,3) , auxl2(nbpmax,7)
263
 
double precision rdevel(nrdeve) , rtuser(nrtuse)
264
 
double precision ra(*)
 
147
double precision dlgeo(nfabor,ngeol)
265
148
 
266
149
! Local variables
267
150
 
268
 
integer          idebia, idebra
269
 
integer          ifinia, ifinra
270
 
 
271
151
integer          ip     , npt    , iok
272
152
integer          nfin   , npars  , iel    , ivf
273
153
integer          npar1  , npar2
274
154
integer          iforce , iitslg
275
 
integer          modntl
 
155
integer          modntl , iromf
276
156
 
277
157
double precision dnpars
278
158
 
 
159
integer          ifac , nn , ifab , ifap , kfap
 
160
integer          n10,n20,n30,n50,n100,nmax
 
161
integer          ius
 
162
 
 
163
double precision distp , d1 , px,py,pz, lvisq, visccf, romf
 
164
double precision tvisq, ustar, ustarmoy
 
165
 
 
166
integer, allocatable, dimension(:) :: indep, ibord
 
167
 
 
168
double precision, allocatable, dimension(:) :: taup
 
169
double precision, allocatable, dimension(:,:) :: tlag, piil
 
170
double precision, allocatable, dimension(:,:) :: vagaus
 
171
double precision, allocatable, dimension(:,:,:) :: bx
 
172
double precision, allocatable, dimension(:,:) :: tsuf, tsup
 
173
double precision, allocatable, dimension(:,:) :: tsvar
 
174
double precision, allocatable, dimension(:,:) :: tempct
 
175
double precision, allocatable, dimension(:) :: tsfext
 
176
double precision, allocatable, dimension(:) :: cpgd1, cpgd2, cpght
 
177
double precision, allocatable, dimension(:,:) :: brgaus
 
178
double precision, allocatable, dimension(:) :: terbru
 
179
double precision, allocatable, dimension(:,:) :: gradpr, gradvf
 
180
double precision, allocatable, dimension(:) :: croule
 
181
double precision, allocatable, dimension(:) :: w1, w2, w3
 
182
double precision, allocatable, dimension(:,:) :: auxl, auxl2
 
183
 
 
184
double precision, allocatable, dimension(:,:) :: tslag
 
185
 
279
186
! NOMBRE DE PASSAGES DANS LA ROUTINE
280
187
 
281
188
integer          ipass
287
194
! 0.  GESTION MEMOIRE ET COMPTEUR DE PASSAGE
288
195
!===============================================================================
289
196
 
 
197
! Allocate temporary arrays
 
198
allocate(indep(nbpmax), ibord(nbpmax))
 
199
allocate(auxl(nbpmax,3))
 
200
allocate(taup(nbpmax))
 
201
allocate(tlag(nbpmax,3))
 
202
allocate(piil(nbpmax,3))
 
203
allocate(vagaus(nbpmax,nvgaus))
 
204
allocate(tsuf(nbpmax,3))
 
205
allocate(tsup(nbpmax,3))
 
206
allocate(bx(nbpmax,3,2))
 
207
allocate(tsvar(nbpmax,nvp1))
 
208
allocate(gradpr(ncelet,3))
 
209
allocate(w1(ncelet), w2(ncelet), w3(ncelet))
 
210
 
 
211
! Allocate other arrays depending on user options
 
212
if ((iphyla.eq.1 .and. itpvar.eq.1) .or. iphyla.eq.2) then
 
213
  allocate(tempct(nbpmax,2))
 
214
endif
 
215
if (iilagr.eq.2) then
 
216
  allocate(tsfext(nbpmax))
 
217
endif
 
218
if (iilagr.eq.2 .and. iphyla.eq.2 .and. ltsthe.eq.1) then
 
219
  allocate(cpgd1(nbpmax))
 
220
  allocate(cpgd2(nbpmax))
 
221
  allocate(cpght(nbpmax))
 
222
endif
 
223
if (modcpl.gt.0) then
 
224
  allocate(gradvf(ncelet,9))
 
225
endif
 
226
if (iroule.eq.1) then
 
227
  allocate(croule(ncelet))
 
228
endif
 
229
if (lamvbr.eq.1) then
 
230
  allocate(brgaus(nbpmax,nbrgau))
 
231
  allocate(terbru(nbpmax))
 
232
endif
 
233
if (nordre.eq.2) then
 
234
  allocate(auxl2(nbpmax,7))
 
235
endif
 
236
 
 
237
 
290
238
ipass = ipass + 1
291
239
 
292
 
idebia = idbia0
293
 
idebra = idbra0
294
240
 
295
241
!===============================================================================
296
242
! 1.  INITIALISATIONS
306
252
npencr = 0
307
253
nbpout = 0
308
254
nbperr = 0
 
255
nbpdep = 0
309
256
 
310
257
dnbpnw = 0.d0
311
258
dnpcsu = 0.d0
314
261
dnpenc = 0.d0
315
262
dnbpou = 0.d0
316
263
dnbper = 0.d0
 
264
dnbdep = 0.d0
317
265
 
318
266
!-->Sur Champ fige Lagrangien : RTPA = RTP
319
267
!   Rem : cette boucle pourrait etre faite au 1er passage
335
283
 
336
284
  call lagdeb                                                     &
337
285
  !==========
338
 
 ( idebia , idebra ,                                              &
339
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
340
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
341
 
   nideve , nrdeve , nituse , nrtuse ,                            &
342
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
343
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
344
 
   icocel , itycel ,                                              &
345
 
   idevel , ituser , ia     ,                                     &
346
 
   rdevel , rtuser , ra     )
 
286
 ( lndnod ,                                                       &
 
287
   icocel , itycel )
 
288
 
 
289
!
 
290
! --> if the deposition model is activated
 
291
!
 
292
 
 
293
  if (idepst.ge.1) then
 
294
 
 
295
     ustarmoy = 0.d0
 
296
     ius = 0
 
297
 
 
298
    ! boundary faces data
 
299
 
 
300
     call laggeo                                                  &
 
301
     !==========
 
302
 ( lndnod ,                                                       &
 
303
   dlgeo  )
 
304
 
 
305
    ! the mesh elements yplus checking
 
306
 
 
307
     n10  = 0
 
308
     n20  = 0
 
309
     n30  = 0
 
310
     n50  = 0
 
311
     n100 = 0
 
312
     nmax = 0
 
313
 
 
314
     do ifac=1, nfabor
 
315
 
 
316
       if (itypfb(ifac).eq.iparoi .or. itypfb(ifac).eq.iparug) then
 
317
 
 
318
         distp = 0.d0
 
319
         iel = ifabor(ifac)
 
320
 
 
321
      ! the density pointer according to the flow location
 
322
 
 
323
         if ( ippmod(icp3pl).ge.0 .or. ippmod(icfuel).ge.0 ) then
 
324
           iromf = ipproc(irom1)
 
325
         else
 
326
           iromf = ipproc(irom)
 
327
         endif
 
328
 
 
329
         romf = propce(iel,iromf)
 
330
         visccf = propce(iel,ipproc(iviscl)) / romf
 
331
 
 
332
         do kfap = itycel(iel), itycel(iel+1)-1
 
333
 
 
334
           ifap = icocel(kfap)
 
335
 
 
336
           if (ifap.gt.0) then
 
337
 
 
338
             do nn = ipnfac(ifap), ipnfac(ifap+1)-1
 
339
 
 
340
               px = xyznod(1,nodfac(nn))
 
341
               py = xyznod(2,nodfac(nn))
 
342
               pz = xyznod(3,nodfac(nn))
 
343
               d1 = abs( px*dlgeo(ifac,1)+py*dlgeo(ifac,2)            &
 
344
                    +pz*dlgeo(ifac,3)+   dlgeo(ifac,4) )              &
 
345
                    /sqrt( dlgeo(ifac,1)*dlgeo(ifac,1)                &
 
346
                    +dlgeo(ifac,2)*dlgeo(ifac,2)                      &
 
347
                    +dlgeo(ifac,3)*dlgeo(ifac,3) )
 
348
 
 
349
               if ( d1 .gt. distp ) then
 
350
                 distp = d1
 
351
               endif
 
352
 
 
353
             enddo
 
354
 
 
355
           else
 
356
 
 
357
             ifab = -ifap
 
358
 
 
359
             do nn = ipnfbr(ifab), ipnfbr(ifab+1)-1
 
360
 
 
361
               px = xyznod(1,nodfbr(nn))
 
362
               py = xyznod(2,nodfbr(nn))
 
363
               pz = xyznod(3,nodfbr(nn))
 
364
 
 
365
               d1 = abs( px*dlgeo(ifac,1)+py*dlgeo(ifac,2)           &
 
366
                        +pz*dlgeo(ifac,3)+ dlgeo(ifac,4))            &
 
367
                  /sqrt( dlgeo(ifac,1)*dlgeo(ifac,1)                 &
 
368
                       + dlgeo(ifac,2)*dlgeo(ifac,2)                 &
 
369
                       + dlgeo(ifac,3)*dlgeo(ifac,3))
 
370
 
 
371
               if ( d1.gt.distp) then
 
372
                 distp = d1
 
373
               endif
 
374
 
 
375
             enddo
 
376
 
 
377
           endif
 
378
 
 
379
         enddo
 
380
 
 
381
         ustar = uetbor(ifac)
 
382
 
 
383
         if (ustar.gt.0.d0) then
 
384
 
 
385
           ustarmoy = ustarmoy + ustar
 
386
           ius = ius + 1
 
387
 
 
388
           lvisq = visccf / ustar
 
389
 
 
390
 
 
391
           distp = distp/lvisq
 
392
 
 
393
           if ( distp .le. 10.d0 ) then
 
394
             n10 = n10+1
 
395
           else if ( distp .le. 20.d0 ) then
 
396
             n20 = n20+1
 
397
           else if ( distp .le. 30.d0 ) then
 
398
             n30 = n30+1
 
399
           else if ( distp .le. 50.d0 ) then
 
400
             n50 = n50+1
 
401
           else if ( distp .le. 100.d0 ) then
 
402
             n100 = n100+1
 
403
           else
 
404
             nmax = nmax +1
 
405
           endif
 
406
 
 
407
         endif
 
408
 
 
409
       endif
 
410
 
 
411
     enddo
 
412
 
 
413
     ustarmoy = ustarmoy / ius
 
414
 
 
415
! the mesh edge yplus and average friction velocity display
 
416
 
 
417
     write(nfecra,4100) nfabor,n10,n20,n30,n50,n100,nmax,ustarmoy
 
418
!
 
419
  endif
347
420
 
348
421
endif
349
422
 
359
432
 
360
433
  call lagent                                                     &
361
434
  !==========
362
 
 ( idebia , idebra ,                                              &
363
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml , nprfml ,   &
364
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
365
 
   nvar   , nscal  , nphas  ,                                     &
 
435
 ( lndnod ,                                                       &
 
436
   nvar   , nscal  ,                                              &
366
437
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
367
438
   ntersl , nvlsta , nvisbr ,                                     &
368
 
   nideve , nrdeve , nituse , nrtuse ,                            &
369
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
370
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
371
 
   itycel     , icocel      ,                                     &
372
 
   ia(iitypf) , ia(iitrif)  , ifrlag , itepa  ,                   &
373
 
   idevel , ituser , ia     ,                                     &
374
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
375
 
   ra(isrfbn) , dt     , rtp    , propce , propfa , propfb ,      &
 
439
   itycel , icocel ,                                              &
 
440
   itypfb , itrifb , ifrlag , itepa  ,                            &
 
441
   dt     , rtp    , propce , propfa , propfb ,                   &
376
442
   coefa  , coefb  ,                                              &
377
 
   ettp   , tepa   , vagaus , auxl   , w1     , w2     , w3     , &
378
 
   rdevel , rtuser , ra     )
 
443
   ettp   , tepa   , vagaus , auxl   , w1     , w2     , w3     )
379
444
 
380
445
else
381
446
 
382
447
  call lagent                                                     &
383
448
  !==========
384
 
 ( idebia , idebra ,                                              &
385
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml , nprfml ,   &
386
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
387
 
   nvar   , nscal  , nphas  ,                                     &
 
449
 ( lndnod ,                                                       &
 
450
   nvar   , nscal  ,                                              &
388
451
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
389
452
   ntersl , nvlsta , nvisbr ,                                     &
390
 
   nideve , nrdeve , nituse , nrtuse ,                            &
391
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
392
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
393
 
   itycel     , icocel      ,                                     &
394
 
   ia(iitypf) , ia(iitrif)  , ifrlag , itepa  ,                   &
395
 
   idevel , ituser , ia     ,                                     &
396
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
397
 
   ra(isrfbn) , dt     , rtpa   , propce , propfa , propfb ,      &
 
453
   itycel , icocel ,                                              &
 
454
   itypfb , itrifb , ifrlag , itepa  ,                            &
 
455
   dt     , rtpa   , propce , propfa , propfb ,                   &
398
456
   coefa  , coefb  ,                                              &
399
 
   ettp   , tepa   , vagaus , auxl   , w1     , w2     , w3     , &
400
 
   rdevel , rtuser , ra     )
 
457
   ettp   , tepa   , vagaus , auxl   , w1     , w2     , w3     )
401
458
endif
402
459
 
403
460
!===============================================================================
408
465
 
409
466
  call uslaru                                                     &
410
467
  !==========
411
 
 ( idebia , idebra ,                                              &
412
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
413
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
414
 
   nvar   , nscal  , nphas  ,                                     &
 
468
 ( nvar   , nscal  ,                                              &
415
469
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
416
470
   ntersl , nvlsta , nvisbr ,                                     &
417
 
   nideve , nrdeve , nituse , nrtuse ,                            &
418
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
419
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
420
 
   ia(iitypf) , ia(iitrif)  , itepa ,                             &
421
 
   idevel , ituser , ia     ,                                     &
422
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
423
 
   ra(isrfbn)  , dt     , rtpa   , propce , propfa , propfb ,     &
 
471
   itypfb , itrifb , itepa ,                                      &
 
472
   dt     , rtpa   , propce , propfa , propfb ,                   &
424
473
   coefa  , coefb  ,                                              &
425
474
   ettp   , tepa   , vagaus , croule , auxl ,                     &
426
 
   ra(idipar) , ra(iyppar) ,                                      &
427
 
   w1     , w2     , w3     ,                                     &
428
 
   rdevel , rtuser , ra     )
 
475
   dispar , yplpar )
429
476
 
430
477
  iok = 0
431
478
  do iel = 1,ncel
472
519
 
473
520
  call laggra                                                     &
474
521
  !==========
475
 
 ( idebia , idebra ,                                              &
476
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
477
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
478
 
   nvar   , nscal  , nphas  ,                                     &
479
 
   nideve , nrdeve , nituse , nrtuse ,                            &
480
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
481
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
482
 
   idevel , ituser , ia     ,                                     &
483
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
522
 ( nvar   , nscal  ,                                              &
484
523
   rtp    , propce , coefa  , coefb  ,                            &
485
 
   gradpr , gradvf ,                                              &
486
 
   w1     , w2     , w3     ,                                     &
487
 
   rdevel , rtuser , ra     )
 
524
   gradpr , gradvf )
488
525
 
489
526
else
490
527
 
491
528
  call laggra                                                     &
492
529
  !==========
493
 
 ( idebia , idebra ,                                              &
494
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
495
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
496
 
   nvar   , nscal  , nphas  ,                                     &
497
 
   nideve , nrdeve , nituse , nrtuse ,                            &
498
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
499
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
500
 
   idevel , ituser , ia     ,                                     &
501
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
530
 ( nvar   , nscal  ,                                              &
502
531
   rtpa   , propce , coefa  , coefb  ,                            &
503
 
   gradpr , gradvf ,                                              &
504
 
   w1     , w2     , w3     ,                                     &
505
 
   rdevel , rtuser , ra     )
 
532
   gradpr , gradvf )
506
533
 
507
534
endif
508
535
 
564
591
 
565
592
  call laggra                                                     &
566
593
  !==========
567
 
 ( idebia , idebra ,                                              &
568
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
569
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
570
 
   nvar   , nscal  , nphas  ,                                     &
571
 
   nideve , nrdeve , nituse , nrtuse ,                            &
572
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
573
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
574
 
   idevel , ituser , ia     ,                                     &
575
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
594
 ( nvar   , nscal  ,                                              &
576
595
   rtp    , propce , coefa  , coefb  ,                            &
577
 
   gradpr , gradvf ,                                              &
578
 
   w1     , w2     , w3     ,                                     &
579
 
   rdevel , rtuser , ra     )
 
596
   gradpr , gradvf )
580
597
 
581
598
endif
582
599
 
588
605
 
589
606
  call lagcar                                                     &
590
607
  !==========
591
 
   ( idebia , idebra ,                                            &
592
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
593
 
     nprfml , nnod   , lndfac , lndfbr , ncelbr ,                 &
594
 
     nvar   , nscal  , nphas  ,                                   &
 
608
   ( nvar   , nscal  ,                                            &
595
609
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
596
610
     ntersl , nvlsta , nvisbr ,                                   &
597
 
     nideve , nrdeve , nituse , nrtuse ,                          &
598
 
     itepa  , idevel , ituser , ia     ,                          &
599
 
     xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,        &
600
 
     volume , dt     , rtpa   , propce , propfa , propfb ,        &
 
611
     itepa  ,                                                     &
 
612
     dt     , rtpa   , propce , propfa , propfb ,                 &
601
613
     ettp   , ettpa  , tepa   , taup   , tlag   ,                 &
602
614
     piil   , bx     , tempct , statis ,                          &
603
 
     gradpr , gradvf , w1     , w2     , auxl(1,1)  ,             &
604
 
     rdevel , rtuser , ra     )
 
615
     gradpr , gradvf , w1     , w2     , auxl(1,1) )
605
616
 
606
617
else
607
618
 
609
620
 
610
621
  call lagcar                                                     &
611
622
  !==========
612
 
   ( idebia , idebra ,                                            &
613
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
614
 
     nprfml , nnod   , lndfac , lndfbr , ncelbr ,                 &
615
 
     nvar   , nscal  , nphas  ,                                   &
 
623
   ( nvar   , nscal  ,                                            &
616
624
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
617
625
     ntersl , nvlsta , nvisbr ,                                   &
618
 
     nideve , nrdeve , nituse , nrtuse ,                          &
619
 
     itepa  , idevel , ituser , ia     ,                          &
620
 
     xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,        &
621
 
     volume , dt     , rtp    , propce , propfa , propfb ,        &
 
626
     itepa  ,                                                     &
 
627
     dt     , rtp    , propce , propfa , propfb ,                 &
622
628
     ettp   , ettpa  , tepa   , taup   , tlag   ,                 &
623
629
     piil   , bx     , tempct , statis ,                          &
624
 
     gradpr , gradvf , w1     , w2     , auxl(1,1) ,              &
625
 
     rdevel , rtuser , ra     )
 
630
     gradpr , gradvf , w1     , w2     , auxl(1,1) )
626
631
 
627
632
endif
628
633
 
630
635
!---> INTEGRATION DES EQUATIONS DIFFERENTIELLES STOCHASTIQUES
631
636
!     POSITION, VITESSE FLUIDE, VITESSE PARTICULE
632
637
 
 
638
 
633
639
call lagesp                                                       &
634
640
!==========
635
 
   ( idebia , idebra ,                                            &
636
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
637
 
     nprfml , nnod   , lndfac , lndfbr , ncelbr ,                 &
638
 
     nvar   , nscal  , nphas  ,                                   &
 
641
   ( nvar   , nscal  , lndnod ,                                   &
639
642
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
640
643
     ntersl , nvlsta , nvisbr ,                                   &
641
 
     nideve , nrdeve , nituse , nrtuse ,                          &
642
 
     itepa  , ibord  , idevel , ituser , ia     ,                 &
643
 
     xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,        &
644
 
     volume ,                                                     &
 
644
     icocel , itycel , ifrlag,                                    &
 
645
     itepa  , ibord  ,                                            &
 
646
     dlgeo  ,                                                     &
645
647
     dt     , rtpa   , rtp    , propce , propfa , propfb ,        &
646
648
     ettp   , ettpa  , tepa   ,                                   &
647
649
     statis , stativ , taup   , tlag   , piil   ,                 &
648
650
     tsuf   , tsup   , bx     , tsfext ,                          &
649
651
     vagaus , gradpr , gradvf , brgaus , terbru ,                 &
650
 
     auxl(1,1) , auxl2 , rdevel , rtuser , ra     )
 
652
     auxl(1,1) , auxl2 )
651
653
 
652
654
!---> INTEGRATION DES EQUATIONS DIFFERENTIELLES STOCHASTIQUES
653
655
!     LIEES AUX PHYSIQUES PARTICULIERES PARTICULAIRES
657
659
  if ( nor.eq.1 ) then
658
660
    call lagphy                                                   &
659
661
    !==========
660
 
    ( idebia , idebra ,                                           &
661
 
      ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,       &
662
 
      nprfml , nvar   , nscal  , nphas  ,                         &
663
 
      nbpmax , nvp    , nvp1   , nvep   , nivep  ,                &
 
662
    ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                &
664
663
      ntersl , nvlsta , nvisbr ,                                  &
665
 
      nideve , nrdeve , nituse , nrtuse ,                         &
666
664
      itepa  , ibord  ,                                           &
667
 
      idevel , ituser , ia     ,                                  &
668
 
      xyzcen , surfac , surfbo , cdgfac , cdgfbo , volume ,       &
669
665
      dt     , rtpa   , propce , propfa , propfb ,                &
670
666
      ettp   , ettpa  , tepa   , taup   , tlag   , tempct ,       &
671
 
      tsvar  , auxl   , cpgd1  , cpgd2  , cpght  ,                &
672
 
      w1     , w2     , w3     ,                                  &
673
 
      rdevel , rtuser , ra     )
 
667
      tsvar  , auxl   , cpgd1  , cpgd2  , cpght  )
674
668
  else
675
669
    call lagphy                                                   &
676
670
    !==========
677
 
    ( idebia , idebra ,                                           &
678
 
      ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,       &
679
 
      nprfml , nvar   , nscal  , nphas  ,                         &
680
 
      nbpmax , nvp    , nvp1   , nvep   , nivep  ,                &
 
671
    ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                &
681
672
      ntersl , nvlsta , nvisbr ,                                  &
682
 
      nideve , nrdeve , nituse , nrtuse ,                         &
683
673
      itepa  , ibord  ,                                           &
684
 
      idevel , ituser , ia     ,                                  &
685
 
      xyzcen , surfac , surfbo , cdgfac , cdgfbo , volume ,       &
686
674
      dt     , rtp    , propce , propfa , propfb ,                &
687
675
      ettp   , ettpa  , tepa   , taup   , tlag   , tempct ,       &
688
 
      tsvar  , auxl   , cpgd1  , cpgd2  , cpght  ,                &
689
 
      w1     , w2     , w3     ,                                  &
690
 
      rdevel , rtuser , ra     )
 
676
      tsvar  , auxl   , cpgd1  , cpgd2  , cpght  )
691
677
  endif
692
678
 
693
679
endif
698
684
 
699
685
if (iilagr.eq.2 .and. nor.eq.nordre) then
700
686
 
701
 
  ifinia = idebia
702
 
  iitslg = idebra
703
 
  ifinra = iitslg + ntersl*nbpmax
704
 
  CALL RASIZE('LAGUNE',IFINRA)
705
 
  !==========
 
687
  ! Allocate a temporary array
 
688
  allocate(tslag(nbpmax,ntersl))
706
689
 
707
690
  call lagcou                                                     &
708
691
  !==========
709
 
   ( ifinia , ifinra ,                                            &
710
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
711
 
     nprfml , nvar   , nscal  , nphas  ,                          &
 
692
   ( nvar   , nscal  ,                                            &
712
693
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
713
694
     ntersl , nvlsta , nvisbr ,                                   &
714
 
     nideve , nrdeve , nituse , nrtuse ,                          &
715
695
     itepa  , indep  , ibord  ,                                   &
716
 
     idevel , ituser , ia     ,                                   &
717
 
     volume , rtp    , propce ,                                   &
 
696
     rtp    , propce ,                                            &
718
697
     ettp   , ettpa  , tepa   , taup   ,                          &
719
698
     tempct , tsfext , tslagr ,                                   &
720
699
     cpgd1  , cpgd2  , cpght  ,                                   &
721
 
     ra(iitslg)      , w1     , w2   ,                            &
722
 
     auxl(1,1) , auxl(1,2)   , auxl(1,3) ,                        &
723
 
     rdevel , rtuser , ra     )
 
700
     tslag  , w1     , w2   ,                                     &
 
701
     auxl(1,1) , auxl(1,2)   , auxl(1,3) )
 
702
 
 
703
     ! Free memory
 
704
     deallocate(tslag)
724
705
 
725
706
endif
726
707
 
733
714
 
734
715
  call lagcel                                                     &
735
716
  !==========
736
 
 ( idebia , idebra ,                                              &
737
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
738
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
739
 
   nvar   , nscal  , nphas  ,                                     &
 
717
 ( lndnod ,                                                       &
 
718
   nvar   , nscal  ,                                              &
740
719
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
741
720
   ntersl , nvlsta , nvisbr ,                                     &
742
 
   nideve , nrdeve , nituse , nrtuse ,                            &
743
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
744
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
745
 
   ia(iitypf)      , ia(iitrif)      ,                            &
 
721
   itypfb , itrifb ,                                              &
746
722
   icocel , itycel , ifrlag , itepa  , ibord  , indep  ,          &
747
 
   idevel , ituser , ia     ,                                     &
748
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
749
 
   ra(isrfbn)      ,                                              &
 
723
   dlgeo  ,                                                       &
750
724
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
751
725
   coefa  , coefb  ,                                              &
752
 
   ettp   , ettpa  , tepa   , parbor , auxl   ,                   &
753
 
   rdevel , rtuser , ra     )
 
726
   ettp   , ettpa  , tepa   , parbor , auxl   )
754
727
 
755
728
  if (ierr.eq.1) then
756
729
    call lagerr
773
746
  !==========
774
747
 ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
775
748
   npars  ,                                                       &
776
 
   nideve , nrdeve , nituse , nrtuse ,                            &
777
749
   itepa  ,                                                       &
778
 
   idevel , ituser , ia     ,                                     &
779
750
   dnpars ,                                                       &
780
 
   ettp   , ettpa  , tepa   ,                                     &
781
 
   rdevel , rtuser , ra )
 
751
   ettp   , ettpa  , tepa   )
782
752
 
783
753
  nbpout = npars
784
754
  dnbpou = dnpars
807
777
 
808
778
  call lagsta                                                     &
809
779
  !==========
810
 
 ( idebia , idebra ,                                              &
811
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
812
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
813
 
   nvar   , nscal  , nphas  ,                                     &
 
780
 ( nvar   , nscal  ,                                              &
814
781
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
815
782
   ntersl , nvlsta , nvisbr ,                                     &
816
 
   nideve , nrdeve , nituse , nrtuse ,                            &
817
783
   itepa  ,                                                       &
818
 
   idevel , ituser , ia     ,                                     &
819
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
820
784
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
821
785
   ettp   , tepa   , statis , stativ ,                            &
822
 
   w1     ,                                                       &
823
 
   rdevel , rtuser , ra     )
 
786
   w1     )
824
787
 
825
788
endif
826
789
 
832
795
 
833
796
  call lagpoi                                                     &
834
797
  !==========
835
 
 ( idebia , idebra ,                                              &
836
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
837
 
   nnod   , lndnod , lndfac , lndfbr , ncelbr ,                   &
838
 
   nvar   , nscal  , nphas  ,                                     &
 
798
 ( lndnod ,                                                       &
 
799
   nvar   , nscal  ,                                              &
839
800
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
840
801
   ntersl , nvlsta , nvisbr ,                                     &
841
 
   nideve , nrdeve , nituse , nrtuse ,                            &
842
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
843
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
844
802
   icocel , itycel , ifrlag , itepa  ,                            &
845
 
   idevel , ituser , ia     ,                                     &
846
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
847
803
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
848
804
   coefa  , coefb  ,                                              &
849
 
   ettp   , tepa   , statis ,                                     &
850
 
   w1     , w2     , w3     ,                                     &
851
 
   rdevel , rtuser , ra     )
 
805
   ettp   , tepa   , statis )
852
806
 
853
807
endif
854
808
 
860
814
 
861
815
  call lagrus                                                     &
862
816
  !==========
863
 
   ( idebia , idebra ,                                            &
864
 
     ncelet , ncel   ,                                            &
 
817
   ( ncelet , ncel   ,                                            &
865
818
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
866
 
     nideve , nrdeve , nituse , nrtuse ,                          &
867
819
     itepa  , indep  ,                                            &
868
 
     idevel , ituser , ia     ,                                   &
869
 
     ettp   , ettpa  , tepa   , croule ,                          &
870
 
     rdevel , rtuser , ra     )
 
820
     ettp   , ettpa  , tepa   , croule )
871
821
 
872
822
  if (npclon.gt.0) then
873
823
 
876
826
 
877
827
    call lagipn                                                   &
878
828
    !==========
879
 
    ( idebia , idebra ,                                           &
880
 
      ncelet , ncel   ,                                           &
 
829
    ( ncelet , ncel   ,                                           &
881
830
      nbpmax , nvp    , nvp1   , nvep   , nivep  ,                &
882
831
      npar1  , npar2  ,                                           &
883
 
      nideve , nrdeve , nituse , nrtuse ,                         &
884
832
      itepa  ,                                                    &
885
 
      idevel , ituser , ia     ,                                  &
886
833
      rtp    ,                                                    &
887
 
      ettp   , tepa   , vagaus ,                                  &
888
 
      w1     , w2     , w3     ,                                  &
889
 
      rdevel , rtuser , ra     )
 
834
      ettp   , tepa   , vagaus )
890
835
 
891
836
  endif
892
837
 
905
850
 
906
851
call uslast                                                       &
907
852
!==========
908
 
 ( idebia , idebra ,                                              &
909
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
910
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
911
 
   nvar   , nscal  , nphas  ,                                     &
 
853
 ( nvar   , nscal  ,                                              &
912
854
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
913
855
   ntersl , nvlsta , nvisbr ,                                     &
914
 
   nideve , nrdeve , nituse , nrtuse ,                            &
915
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
916
 
   ipnfac , nodfac , ipnfbr , nodfbr , itepa  ,                   &
917
 
   idevel , ituser , ia     ,                                     &
918
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
856
   itepa  ,                                                       &
919
857
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
920
858
   coefa  , coefb  ,                                              &
921
859
   ettp   , ettpa  , tepa   , taup   , tlag   , tempct ,          &
922
 
   statis , stativ ,                                              &
923
 
   w1     , w2     , w3     ,                                     &
924
 
   rdevel , rtuser , ra     )
 
860
   statis , stativ )
925
861
 
926
862
!===============================================================================
927
863
! 16. Visualisations
939
875
 
940
876
  call enslag                                                     &
941
877
  !==========
942
 
   ( idebia , idebra ,                                            &
943
 
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
 
878
   ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
944
879
     nfin   , iforce ,                                            &
945
880
     itepa  ,                                                     &
946
 
     ettp   , tepa   , ra )
 
881
     ettp   , tepa   )
947
882
endif
948
883
 
949
884
if (iensi2.eq.1) then
952
887
   ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
953
888
     nfin   ,                                                     &
954
889
     itepa  ,                                                     &
955
 
     ettp   , tepa , auxl   )
 
890
     ettp   , tepa   )
956
891
endif
957
892
 
958
893
!===============================================================================
983
918
if (modntl.eq.0) then
984
919
   call lagaff                                                    &
985
920
   !==========
986
 
 ( idebia , idebra ,                                              &
987
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
988
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
989
 
   nvar   , nscal  , nphas  ,                                     &
 
921
 ( nvar   , nscal  ,                                              &
990
922
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
991
923
   ntersl , nvlsta , nvisbr ,                                     &
992
 
   nideve , nrdeve , nituse , nrtuse ,                            &
993
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
994
 
   ipnfac , nodfac , ipnfbr , nodfbr , itepa  ,                   &
995
 
   idevel , ituser , ia     ,                                     &
996
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
924
   itepa  ,                                                       &
997
925
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
998
926
   coefa  , coefb  ,                                              &
999
 
   ettp   , ettpa  , tepa   , taup   , tlag   , tempct , statis , &
1000
 
   w1     , w2     , w3     ,                                     &
1001
 
   rdevel , rtuser , ra     )
1002
 
 
 
927
   ettp   , ettpa  , tepa   , taup   , tlag   , tempct , statis )
 
928
 
 
929
endif
 
930
 
 
931
! Free memory
 
932
deallocate(indep, ibord)
 
933
deallocate(auxl)
 
934
deallocate(taup)
 
935
deallocate(tlag)
 
936
deallocate(piil)
 
937
deallocate(vagaus)
 
938
deallocate(tsuf)
 
939
deallocate(tsup)
 
940
deallocate(bx)
 
941
deallocate(tsvar)
 
942
deallocate(gradpr)
 
943
deallocate(w1, w2, w3)
 
944
if ((iphyla.eq.1 .and. itpvar.eq.1) .or. iphyla.eq.2) then
 
945
  deallocate(tempct)
 
946
endif
 
947
if (iilagr.eq.2) then
 
948
  deallocate(tsfext)
 
949
endif
 
950
if (iilagr.eq.2 .and. iphyla.eq.2 .and. ltsthe.eq.1) then
 
951
  deallocate(cpgd1)
 
952
  deallocate(cpgd2)
 
953
  deallocate(cpght)
 
954
endif
 
955
if (modcpl.gt.0) then
 
956
  deallocate(gradvf)
 
957
endif
 
958
if (iroule.eq.1) then
 
959
  deallocate(croule)
 
960
endif
 
961
if (lamvbr.eq.1) then
 
962
  deallocate(brgaus)
 
963
  deallocate(terbru)
 
964
endif
 
965
if (nordre.eq.2) then
 
966
  deallocate(auxl2)
1003
967
endif
1004
968
 
1005
969
!===============================================================================
1029
993
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
1030
994
'@                                                            ',/)
1031
995
 
 
996
 4100 format(                                                     &
 
997
'                                                               '/,&
 
998
'   ** LAGRANGIAN MODULE:  '                                     /,&
 
999
'   ** Check of the mesh for the deposition submodel  '         ,/,&
 
1000
'      ---------------------------------------------  '         ,/,&
 
1001
'                                                               '/,&
 
1002
' Number of boundary faces                        ',I10         ,/,&
 
1003
' Number of boundary faces with 0  < y^+ < 10     ',I10         ,/,&
 
1004
' Number of boundary faces with 10 < y^+ < 20     ',I10         ,/,&
 
1005
' Number of boundary faces with 20 < y^+ < 30     ',I10         ,/,&
 
1006
' Number of boundary faces with 30 < y^+ < 50     ',I10         ,/,&
 
1007
' Number of boundary faces with 50 < y^+ < 100    ',I10         ,/,&
 
1008
' Number of boundary faces with y^+ > 100         ',I10         ,/,&
 
1009
'                                                               '/,&
 
1010
'   ** Mean friction velocity  (ustar) =  ',F7.3                ,/,&
 
1011
'---------------------------------------------------------------  ',/)
 
1012
 
1032
1013
!----
1033
1014
! FIN
1034
1015
!----