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

« back to all changes in this revision

Viewing changes to users/base/usalcl.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:
2
2
 
3
3
!VERS
4
4
 
5
 
 
6
 
!     This file is part of the Code_Saturne Kernel, element of the
7
 
!     Code_Saturne CFD tool.
8
 
 
9
 
!     Copyright (C) 1998-2010 EDF S.A., France
10
 
 
11
 
!     contact: saturne-support@edf.fr
12
 
 
13
 
!     The Code_Saturne Kernel is free software; you can redistribute it
14
 
!     and/or modify it under the terms of the GNU General Public License
15
 
!     as published by the Free Software Foundation; either version 2 of
16
 
!     the License, or (at your option) any later version.
17
 
 
18
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
19
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
20
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21
 
!     GNU General Public License for more details.
22
 
 
23
 
!     You should have received a copy of the GNU General Public License
24
 
!     along with the Code_Saturne Kernel; if not, write to the
25
 
!     Free Software Foundation, Inc.,
26
 
!     51 Franklin St, Fifth Floor,
27
 
!     Boston, MA  02110-1301  USA
 
5
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
6
!
 
7
! Copyright (C) 1998-2011 EDF S.A.
 
8
!
 
9
! This program is free software; you can redistribute it and/or modify it under
 
10
! the terms of the GNU General Public License as published by the Free Software
 
11
! Foundation; either version 2 of the License, or (at your option) any later
 
12
! version.
 
13
!
 
14
! This program is distributed in the hope that it will be useful, but WITHOUT
 
15
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
16
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
17
! details.
 
18
!
 
19
! You should have received a copy of the GNU General Public License along with
 
20
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
21
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
28
22
 
29
23
!-------------------------------------------------------------------------------
30
24
 
31
25
subroutine usalcl &
32
26
!================
33
27
 
34
 
 ( idbia0 , idbra0 , itrale ,                                     &
35
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
36
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
37
 
   nvar   , nscal  , nphas  ,                                     &
38
 
   nideve , nrdeve , nituse , nrtuse ,                            &
39
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml , maxelt , lstelt , &
40
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
 
28
 ( itrale ,                                                       &
 
29
   nvar   , nscal  ,                                              &
41
30
   icodcl , itypfb , ialtyb , impale ,                            &
42
 
   idevel , ituser , ia     ,                                     &
43
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
44
31
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
45
 
   coefa  , coefb  , rcodcl , xyzno0 , depale ,                   &
46
 
   rdevel , rtuser , ra     )
 
32
   coefa  , coefb  , rcodcl , xyzno0 , depale )
47
33
 
48
34
!===============================================================================
49
35
! Purpose:
292
278
! Arguments
293
279
!__________________.____._____.________________________________________________.
294
280
! name             !type!mode ! role                                           !
295
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
296
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
297
281
! itrale           ! i  ! <-- ! number of iterations for ALE method            !
298
 
! ndim             ! i  ! <-- ! spatial dimension                              !
299
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
300
 
! ncel             ! i  ! <-- ! number of cells                                !
301
 
! nfac             ! i  ! <-- ! number of interior faces                       !
302
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
303
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
304
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
305
 
! nnod             ! i  ! <-- ! number of vertices                             !
306
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
307
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
308
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
309
282
! nvar             ! i  ! <-- ! total number of variables                      !
310
283
! nscal            ! i  ! <-- ! total number of scalars                        !
311
 
! nphas            ! i  ! <-- ! number of phases                               !
312
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
313
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
314
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
315
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
316
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
317
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
318
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
319
 
!  (nfml, nprfml)  !    !     !                                                !
320
 
! maxelt           ! i  ! <-- ! max number of cells and faces (int/boundary)   !
321
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
322
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
323
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
324
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
325
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
326
284
! icodcl           ! ia ! --> ! boundary condition code                        !
327
285
!  (nfabor, nvar)  !    !     ! = 1  -> Dirichlet                              !
328
286
!                  !    !     ! = 2  -> flux density                           !
332
290
!                  !    !     ! = 9  -> free inlet/outlet (velocity)           !
333
291
!                  !    !     !         inflowing possibly blocked             !
334
292
! itypfb           ! ia ! --> ! boundary face types                            !
335
 
!  (nfabor, nphas) !    !     !                                                !
336
293
! ialtyb (nfabor)  ! ia ! --> ! boundary face types for mesh velocity          !
337
294
! impale(nnod)     ! ia ! <-- ! indicator for fixed node displacement          !
338
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
339
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
340
 
! ia(*)            ! ia ! --- ! main integer work array                        !
341
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
342
 
!  (ndim, ncelet)  !    !     !                                                !
343
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
344
 
!  (ndim, nfac)    !    !     !                                                !
345
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
346
 
!  (ndim, nfabor)  !    !     !                                                !
347
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
348
 
!  (ndim, nfac)    !    !     !                                                !
349
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
350
 
!  (ndim, nfabor)  !    !     !                                                !
351
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
352
 
!  (ndim, nnod)    !    !     !                                                !
353
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
354
295
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
355
296
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
356
297
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
372
313
! depale(nnod,3)   ! ra ! <-- ! nodes displacement                             !
373
314
! xyzno0           ! ra ! <-- ! vertex coordinates of initial mesh             !
374
315
!  (3, nnod)       !    !     !                                                !
375
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
376
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
377
 
! ra(*)            ! ra ! --- ! main real work array                           !
378
316
!__________________!____!_____!________________________________________________!
379
317
 
380
318
!     Type: i (integer), r (real), s (string), a (array), l (logical),
382
320
!     mode: <-- input, --> output, <-> modifies data, --- work array
383
321
!===============================================================================
384
322
 
 
323
!===============================================================================
 
324
! Module files
 
325
!===============================================================================
 
326
 
 
327
use paramx
 
328
use numvar
 
329
use optcal
 
330
use cstphy
 
331
use cstnum
 
332
use entsor
 
333
use parall
 
334
use period
 
335
use ihmpre
 
336
use mesh
 
337
 
 
338
!===============================================================================
 
339
 
385
340
implicit none
386
341
 
387
 
!===============================================================================
388
 
! Common blocks
389
 
!===============================================================================
390
 
 
391
 
include "paramx.h"
392
 
include "pointe.h"
393
 
include "numvar.h"
394
 
include "optcal.h"
395
 
include "cstphy.h"
396
 
include "cstnum.h"
397
 
include "entsor.h"
398
 
include "parall.h"
399
 
include "period.h"
400
 
include "ihmpre.h"
401
 
 
402
 
!===============================================================================
403
 
 
404
342
! Arguments
405
343
 
406
 
integer          idbia0 , idbra0 , itrale
407
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
408
 
integer          nfml   , nprfml
409
 
integer          nnod   , lndfac , lndfbr , ncelbr
410
 
integer          nvar   , nscal  , nphas
411
 
integer          nideve , nrdeve , nituse , nrtuse
 
344
integer          itrale
 
345
integer          nvar   , nscal
412
346
 
413
 
integer          ifacel(2,nfac) , ifabor(nfabor)
414
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
415
 
integer          iprfml(nfml,nprfml)
416
 
integer          maxelt, lstelt(maxelt)
417
 
integer          ipnfac(nfac+1), nodfac(lndfac)
418
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
419
347
integer          icodcl(nfabor,nvar)
420
 
integer          itypfb(nfabor,nphas), ialtyb(nfabor)
 
348
integer          itypfb(nfabor), ialtyb(nfabor)
421
349
integer          impale(nnod)
422
 
integer          idevel(nideve), ituser(nituse), ia(*)
423
350
 
424
 
double precision xyzcen(ndim,ncelet)
425
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
426
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
427
 
double precision xyznod(ndim,nnod), volume(ncelet)
428
351
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
429
352
double precision propce(ncelet,*)
430
353
double precision propfa(nfac,*), propfb(nfabor,*)
431
354
double precision coefa(nfabor,*), coefb(nfabor,*)
432
355
double precision rcodcl(nfabor,nvar,3)
433
356
double precision depale(nnod,3), xyzno0(3,nnod)
434
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
435
357
 
436
358
! Local variables
437
359
 
438
 
integer          idebia, idebra
439
360
integer          ifac, iel, ii
440
361
integer          inod
441
362
integer          ilelt, nlelt
442
363
 
443
364
double precision delta, deltaa
444
365
 
 
366
integer, allocatable, dimension(:) :: lstelt
 
367
 
445
368
!===============================================================================
446
369
 
447
370
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
477
400
 
478
401
!===============================================================================
479
402
! 1.  Initialization
480
 
 
481
403
!===============================================================================
482
404
 
483
 
idebia = idbia0
484
 
idebra = idbra0
 
405
! Allocate a temporary array for boundary faces selection
 
406
allocate(lstelt(nfabor))
 
407
 
485
408
 
486
409
 
487
410
!===============================================================================
570
493
! FIN
571
494
!----
572
495
 
 
496
! Deallocate the temporary array
 
497
deallocate(lstelt)
 
498
 
573
499
return
574
500
end subroutine