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

« back to all changes in this revision

Viewing changes to src/lagr/lagesp.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 lagesp &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
34
 
   nvar   , nscal  , nphas  ,                                     &
 
26
 ( nvar   , nscal  , lndnod ,                                     &
35
27
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
36
28
   ntersl , nvlsta , nvisbr ,                                     &
37
 
   nideve , nrdeve , nituse , nrtuse ,                            &
38
 
   itepa  , ibord  , idevel , ituser , ia     ,                   &
39
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
29
   icocel , itycel, ifrlag,                                       &
 
30
   itepa  , ibord  ,                                              &
 
31
   dlgeo  ,                                                       &
40
32
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
41
33
   ettp   , ettpa  , tepa   , statis , stativ ,                   &
42
34
   taup   , tlag   , piil   ,                                     &
43
35
   tsuf   , tsup   , bx     , tsfext ,                            &
44
 
   vagaus , gradpr , gradvf , brgaus , terbru , romp   , auxl2  , &
45
 
   rdevel , rtuser , ra     )
 
36
   vagaus , gradpr , gradvf , brgaus , terbru , romp   , auxl2  )
46
37
 
47
38
!===============================================================================
48
 
! FONCTION :
 
39
! Purpose:
49
40
! ----------
50
41
 
51
 
!   SOUS-PROGRAMME DU MODULE LAGRANGIEN :
52
 
!   -------------------------------------
53
 
 
54
 
!    INTEGRATION DES EDS PAR UN SCHEMA D'ORDRE 2 : LAGES2
55
 
!    INTEGRATION DES EDS PAR UN SCHEMA D'ORDRE 1 : LAGES1
56
 
 
 
42
!   Subroutine of the Lagrangian particle-tracking module :
 
43
!   ------------------------------------------------------
 
44
 
 
45
!   Integration of particle equations of motion :
 
46
!
 
47
!   * Standard Model : First order  -> call of subroutine lages1
 
48
!                      Second order -> call of subroutine lages2
 
49
!
 
50
!   * Deposition submodel (Guingo & Minier, 2008) if needed
 
51
!
57
52
!-------------------------------------------------------------------------------
58
53
! Arguments
59
54
!__________________.____._____.________________________________________________.
60
55
! name             !type!mode ! role                                           !
61
56
!__________________!____!_____!________________________________________________!
62
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
63
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
64
 
! ndim             ! i  ! <-- ! spatial dimension                              !
65
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
66
 
! ncel             ! i  ! <-- ! number of cells                                !
67
 
! nfac             ! i  ! <-- ! number of interior faces                       !
68
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
69
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
70
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
71
 
! nnod             ! i  ! <-- ! number of vertices                             !
72
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
73
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
74
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
 
57
! lndnod           ! e  ! <-- ! dim. connectivite cellules->faces              !
75
58
! nvar             ! i  ! <-- ! total number of variables                      !
76
59
! nscal            ! i  ! <-- ! total number of scalars                        !
77
 
! nphas            ! i  ! <-- ! number of phases                               !
78
60
! nbpmax           ! e  ! <-- ! nombre max de particulies autorise             !
79
61
! nvp              ! e  ! <-- ! nombre de variables particulaires              !
80
62
! nvp1             ! e  ! <-- ! nvp sans position, vfluide, vpart              !
83
65
! ntersl           ! e  ! <-- ! nbr termes sources de couplage retour          !
84
66
! nvlsta           ! e  ! <-- ! nombre de var statistiques lagrangien          !
85
67
! nvisbr           ! e  ! <-- ! nombre de statistiques aux frontieres          !
86
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
87
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
 
68
! icocel           ! te ! --> ! connectivite cellules -> faces                 !
 
69
!   (lndnod)       !    !     !    face de bord si numero negatif              !
 
70
! itycel           ! te ! --> ! connectivite cellules -> faces                 !
 
71
!   (ncelet+1)     !    !     !    pointeur du tableau icocel                  !
 
72
! ifrlag           ! te ! --> ! numero de zone de la face de bord              !
 
73
!   (nfabor)       !    !     !  pour le module lagrangien                     !
88
74
! itepa            ! te ! <-- ! info particulaires (entiers)                   !
89
75
! (nbpmax,nivep    !    !     !   (cellule de la particule,...)                !
90
76
! ibord            ! te ! --> ! si nordre=2, contient le numero de la          !
91
77
!   (nbpmax)       !    !     !   face d'interaction part/frontiere            !
92
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
93
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
94
 
! ia(*)            ! ia ! --- ! main integer work array                        !
95
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
96
 
!  (ndim, ncelet)  !    !     !                                                !
97
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
98
 
!  (ndim, nfac)    !    !     !                                                !
99
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
100
 
!  (ndim, nfabor)  !    !     !                                                !
101
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
102
 
!  (ndim, nfac)    !    !     !                                                !
103
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
104
 
!  (ndim, nfabor)  !    !     !                                                !
105
 
! xyznod           ! tr ! <-- ! coordonnes des noeuds                          !
106
 
! (ndim,nnod)      !    !     !                                                !
107
 
! volume(ncelet    ! tr ! <-- ! volume d'un des ncelet elements                !
 
78
! dlgeo            ! tr ! --> ! tableau contenant les donnees geometriques     !
 
79
! (nfabor,ngeol)   !    !     ! pour le sous-modele de depot                   !
108
80
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
109
81
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
110
82
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
138
110
! romp             ! tr ! --- ! masse volumique des particules                 !
139
111
! auxl2            ! tr ! --- ! tableau de travail                             !
140
112
!    (nbpmax,7)    !    !     !                                                !
141
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
142
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
143
 
! ra(*)            ! ra ! --- ! main real work array                           !
144
113
!__________________!____!_____!________________________________________________!
145
114
 
146
115
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
147
116
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
148
117
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
149
118
!            --- tableau de travail
 
119
!===============================================================================
 
120
 
 
121
!===============================================================================
 
122
! Module files
 
123
!===============================================================================
 
124
 
 
125
use paramx
 
126
use numvar
 
127
use cstphy
 
128
use cstnum
 
129
use optcal
 
130
use entsor
 
131
use lagpar
 
132
use lagran
 
133
use ppppar
 
134
use ppthch
 
135
use mesh
150
136
 
151
137
!===============================================================================
152
138
 
153
139
implicit none
154
140
 
155
 
!===============================================================================
156
 
! Common blocks
157
 
!===============================================================================
158
 
 
159
 
include "paramx.h"
160
 
include "numvar.h"
161
 
include "cstphy.h"
162
 
include "cstnum.h"
163
 
include "optcal.h"
164
 
include "entsor.h"
165
 
include "lagpar.h"
166
 
include "lagran.h"
167
 
include "ppppar.h"
168
 
include "ppthch.h"
169
 
 
170
 
!===============================================================================
171
 
 
172
141
! Arguments
173
142
 
174
 
integer          idbia0 , idbra0
175
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
176
 
integer          nfml   , nprfml
177
 
integer          nnod   , lndfac , lndfbr , ncelbr
178
 
integer          nvar   , nscal  , nphas
 
143
integer          nvar   , nscal
179
144
integer          nbpmax , nvp    , nvp1   , nvep  , nivep
180
 
integer          ntersl , nvlsta , nvisbr
181
 
integer          nideve , nrdeve , nituse , nrtuse
 
145
integer          ntersl , nvlsta , nvisbr , lndnod
 
146
 
182
147
integer          itepa(nbpmax,nivep) , ibord(nbpmax)
183
 
integer          idevel(nideve), ituser(nituse)
184
 
integer          ia(*)
 
148
integer          icocel(lndnod),  ifrlag(nfabor), itycel(ncelet+1)
185
149
 
186
 
double precision xyzcen(ndim,ncelet)
187
 
double precision surfac(ndim,nfac) , surfbo(ndim,nfabor)
188
 
double precision cdgfac(ndim,nfac) , cdgfbo(ndim,nfabor)
189
 
double precision xyznod(ndim,nnod) , volume(ncelet)
190
150
double precision dt(ncelet) , rtp(ncelet,*) , rtpa(ncelet,*)
191
151
double precision propce(ncelet,*)
192
152
double precision propfa(nfac,*) , propfb(nfabor,*)
197
157
double precision piil(nbpmax,3) , bx(nbpmax,3,2)
198
158
double precision tsuf(nbpmax,3) , tsup(nbpmax,3)
199
159
double precision tsfext(nbpmax)
 
160
double precision dlgeo(nfabor,ngeol)
200
161
double precision vagaus(nbpmax,*)
201
162
double precision gradpr(ncelet,3) , gradvf(ncelet,9)
202
163
double precision brgaus(nbpmax,*) , terbru(nbpmax)
203
164
double precision romp(nbpmax) , auxl2(nbpmax,7)
204
 
double precision rdevel(nrdeve), rtuser(nrtuse)
205
 
double precision ra(*)
206
165
 
207
166
! Local variables
208
167
 
209
 
integer          idebia , idebra
210
 
integer          ip , ifinia , ifinra, ifexla
 
168
integer          iel , ifac , ip
 
169
integer          iauxp , nbfac
 
170
integer          icrit , itirag , inb , iifacl
 
171
integer           ii
 
172
 
211
173
double precision d3 , aa
212
174
 
213
 
!===============================================================================
214
 
 
215
 
!===============================================================================
216
 
! 0.  GESTION MEMOIRE
217
 
!===============================================================================
218
 
 
219
 
idebia = idbia0
220
 
idebra = idbra0
221
 
 
222
 
!===============================================================================
223
 
! 1.  INITIALISATION
224
 
!===============================================================================
225
 
 
226
 
! Calcul de la masse volumique des particules
 
175
double precision, allocatable, dimension(:,:) :: fextla
 
176
 
 
177
!===============================================================================
 
178
 
 
179
!===============================================================================
 
180
! 0.  Memory management
 
181
!===============================================================================
 
182
 
 
183
 
 
184
!===============================================================================
 
185
! 1.  Initialization
 
186
!===============================================================================
 
187
! Initialize variables to avoid compiler warnings
 
188
 
 
189
iifacl = 0
 
190
 
 
191
 
 
192
! Computation of particle density
227
193
 
228
194
aa = 6.d0 / pi
229
195
do ip = 1,nbpart
234
200
enddo
235
201
 
236
202
!===============================================================================
237
 
! 2.  PRISE EN COMPTE DES FORCES UTILISATEURS EXTERIEURES
 
203
! 2.  Management of user external force fields
238
204
!===============================================================================
239
205
 
240
 
ifinia = idebia
241
 
ifexla = idebra
242
 
ifinra = ifexla + 3*nbpmax
243
 
CALL RASIZE('LAGESP',IFINRA)
244
 
!==========
 
206
! Allocate a temporay array
 
207
allocate(fextla(nbpmax,3))
245
208
 
246
 
do ip = 1,3*nbpmax
247
 
  ra(ifexla+ip-1) = 0.d0
 
209
do ip = 1, nbpmax
 
210
  fextla(ip,1) = 0.d0
 
211
  fextla(ip,2) = 0.d0
 
212
  fextla(ip,3) = 0.d0
248
213
enddo
249
214
 
250
215
call uslafe                                                       &
251
216
!==========
252
 
 ( ifinia , ifinra ,                                              &
253
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
254
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
255
 
   nvar   , nscal  , nphas  ,                                     &
 
217
 ( nvar   , nscal  ,                                              &
256
218
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
257
219
   ntersl , nvlsta , nvisbr ,                                     &
258
 
   nideve , nrdeve , nituse , nrtuse ,                            &
259
 
   itepa  , ibord  , idevel , ituser , ia     ,                   &
260
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
220
   itepa  , ibord  ,                                              &
261
221
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
262
222
   ettp   , ettpa  , tepa   , statis , stativ ,                   &
263
223
   taup   , tlag   , piil   ,                                     &
264
224
   tsuf   , tsup   , bx     , tsfext ,                            &
265
225
   vagaus , gradpr , gradvf ,                                     &
266
 
   romp   , ra(ifexla) ,                                          &
267
 
   rdevel , rtuser , ra     )
 
226
   romp   , fextla )
268
227
 
269
228
!===============================================================================
270
 
! 3.  PRISE EN COMPTE DES FORCES CHIMIQUES
271
 
!       - Forces de Van der Vaals
272
 
!       - Forces electrostatiques
 
229
! 3.  Management of physici-chemical forces (DLVO theory)
 
230
!       - Van der Waals forces
 
231
!       - Electrostatic forces
273
232
!===============================================================================
274
233
 
275
234
if ( ladlvo .eq. 1 ) then
276
235
 
277
236
  call lagfch                                                     &
278
237
  !==========
279
 
 ( ifinia , ifinra ,                                              &
280
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
281
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
282
 
   nvar   , nscal  , nphas  ,                                     &
 
238
 ( nvar   , nscal  ,                                              &
283
239
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
284
240
   ntersl , nvlsta , nvisbr ,                                     &
285
 
   nideve , nrdeve , nituse , nrtuse ,                            &
286
 
   itepa  , ibord  , idevel , ituser , ia     ,                   &
287
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
241
   itepa  , ibord  ,                                              &
288
242
   dt     , rtpa   , rtp    , propce , propfa , propfb ,          &
289
243
   ettp   , ettpa  , tepa   , statis , stativ ,                   &
290
244
   taup   , tlag   , piil   ,                                     &
291
245
   tsuf   , tsup   , bx     , tsfext ,                            &
292
246
   vagaus , gradpr , gradvf ,                                     &
293
 
   romp   , ra(ifexla)      ,                                     &
294
 
   rdevel , rtuser , ra     )
 
247
   romp   , fextla )
295
248
 
296
249
 endif
297
250
 
298
251
!===============================================================================
299
 
! 4.  ORDRE 1
 
252
! 4.  First order
300
253
!===============================================================================
301
254
 
302
255
if (nordre.eq.1) then
303
256
 
 
257
!=============================================================================
 
258
! 4.1 If no deposition sub-model is activated, call of subroutine lages1
 
259
!     for every particle
 
260
!=============================================================================
 
261
 
 
262
  if (idepst.le.0) then
 
263
 
304
264
  call lages1                                                     &
305
265
  !==========
306
 
   ( ifinia , ifinra ,                                            &
307
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
308
 
     nprfml , nnod   , lndfac , lndfbr , ncelbr ,                 &
309
 
     nvar   , nscal  , nphas  ,                                   &
310
 
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
311
 
     ntersl , nvlsta , nvisbr ,                                   &
312
 
     nideve , nrdeve , nituse , nrtuse ,                          &
313
 
     itepa  , idevel , ituser , ia     ,                          &
314
 
     xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,        &
315
 
     volume ,                                                     &
316
 
     dt     , rtpa   , propce , propfa , propfb ,                 &
317
 
     ettp   , ettpa  , tepa   ,                                   &
318
 
     statis , taup   , tlag   , piil   ,                          &
319
 
     bx     , vagaus , gradpr , gradvf , romp   ,                 &
320
 
     brgaus , terbru , ra(ifexla) ,                               &
321
 
     rdevel , rtuser , ra     )
 
266
   ( nvar   , nscal  ,                                            &
 
267
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
 
268
     ntersl , nvlsta , nvisbr ,                                   &
 
269
     itepa  ,                                                     &
 
270
     dt     , rtpa   , propce , propfa , propfb ,                 &
 
271
     ettp   , ettpa  , tepa   ,                                   &
 
272
     statis , taup   , tlag   , piil   ,                          &
 
273
     bx     , vagaus , gradpr , gradvf , romp   ,                 &
 
274
     brgaus , terbru , fextla )
 
275
 
 
276
 
 
277
!=============================================================================
 
278
! 4.2 Management of the deposition submodel
 
279
!=============================================================================
 
280
 
 
281
  else
 
282
 
 
283
     call lagdep                                                  &
 
284
    !==========
 
285
   ( nvar   , nscal  , lndnod , icocel , itycel, ifrlag ,         &
 
286
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
 
287
     ntersl , nvlsta , nvisbr ,                                   &
 
288
     itepa  ,                                                     &
 
289
     dlgeo  ,                                                     &
 
290
     dt     , rtpa   , propce , propfa , propfb ,                 &
 
291
     ettp   , ettpa  , tepa   ,                                   &
 
292
     statis , taup   , tlag   , piil   ,                          &
 
293
     bx     , vagaus , gradpr , gradvf , romp   ,                 &
 
294
     brgaus , terbru , fextla )
 
295
 
 
296
  endif
322
297
 
323
298
!===============================================================================
324
 
! 5.  ORDRE 2
 
299
! 5.  Second order
325
300
!===============================================================================
326
301
 
327
302
else
328
303
 
329
304
  call lages2                                                     &
330
305
  !==========
331
 
   ( ifinia , ifinra ,                                            &
332
 
     ndim   , ncelet , ncel   , nfac   , nfabor , nfml   ,        &
333
 
     nprfml , nnod   , lndfac , lndfbr , ncelbr ,                 &
334
 
     nvar   , nscal  , nphas  ,                                   &
 
306
   ( nvar   , nscal  ,                                            &
335
307
     nbpmax , nvp    , nvp1   , nvep   , nivep  ,                 &
336
308
     ntersl , nvlsta , nvisbr ,                                   &
337
 
     nideve , nrdeve , nituse , nrtuse ,                          &
338
 
     itepa  , ibord  , idevel , ituser , ia     ,                 &
339
 
     xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,        &
340
 
     volume ,                                                     &
 
309
     itepa  , ibord  ,                                            &
341
310
     dt     , rtpa   , rtp    , propce , propfa , propfb ,        &
342
311
     ettp   , ettpa  , tepa   ,                                   &
343
312
     statis , taup   , tlag   , piil   ,                          &
344
313
     tsuf   , tsup   , bx     , tsfext , vagaus ,                 &
345
314
     auxl2  , gradpr , gradvf ,                                   &
346
 
     romp   , brgaus , terbru , ra(ifexla) ,                      &
347
 
     rdevel , rtuser , ra     )
 
315
     romp   , brgaus , terbru , fextla )
348
316
 
349
317
endif
350
318
 
 
319
! Free memory
 
320
deallocate(fextla)
 
321
 
351
322
!===============================================================================
352
323
 
353
324
end subroutine