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

« back to all changes in this revision

Viewing changes to users/base/usvima.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-01 17:43:32 UTC
  • mto: (6.1.7 sid)
  • mto: This revision was merged to the branch mainline in revision 11.
  • Revision ID: package-import@ubuntu.com-20111101174332-tl4vk45no0x3emc3
Tags: upstream-2.1.0
ImportĀ upstreamĀ versionĀ 2.1.0

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-2009 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 usvima &
32
26
!================
33
27
 
34
 
 ( idbia0 , idbra0 ,                                              &
35
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
36
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
37
 
   nvar   , nscal  ,                                              &
38
 
   nideve , nrdeve , nituse , nrtuse ,                            &
39
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
40
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
41
 
   idevel , ituser , ia     ,                                     &
42
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
28
 ( nvar   , nscal  ,                                              &
43
29
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
44
30
   coefa  , coefb  ,                                              &
45
 
   viscmx , viscmy , viscmz ,                                     &
46
 
   w1     , w2     , w3     , w4     ,                            &
47
 
   w5     , w6     , w7     , w8     ,                            &
48
 
   rdevel , rtuser , ra     )
 
31
   viscmx , viscmy , viscmz )
49
32
 
50
33
!===============================================================================
51
34
! Purpose:
79
62
!__________________.____._____.________________________________________________.
80
63
! name             !type!mode ! role                                           !
81
64
!__________________!____!_____!________________________________________________!
82
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
83
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
84
 
! ndim             ! i  ! <-- ! spatial dimension                              !
85
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
86
 
! ncel             ! i  ! <-- ! number of cells                                !
87
 
! nfac             ! i  ! <-- ! number of interior faces                       !
88
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
89
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
90
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
91
 
! nnod             ! i  ! <-- ! number of vertices                             !
92
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
93
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
94
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
95
65
! nvar             ! i  ! <-- ! total number of variables                      !
96
66
! nscal            ! i  ! <-- ! total number of scalars                        !
97
 
! nphas            ! i  ! <-- ! number of phases                               !
98
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
99
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
100
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
101
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
102
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
103
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
104
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
105
 
!  (nfml, nprfml)  !    !     !                                                !
106
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
107
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
108
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
109
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
110
 
! idevel(nideve)   ! ia ! <-- ! integer work array for temporary developpement !
111
 
! ituser(nituse)   ! ia ! <-- ! user-reserved integer work array               !
112
 
! ia(*)            ! ia ! --- ! main integer work array                        !
113
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
114
 
!  (ndim, ncelet)  !    !     !                                                !
115
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
116
 
!  (ndim, nfac)    !    !     !                                                !
117
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
118
 
!  (ndim, nfavor)  !    !     !                                                !
119
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
120
 
!  (ndim, nfac)    !    !     !                                                !
121
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
122
 
!  (ndim, nfabor)  !    !     !                                                !
123
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
124
 
!  (ndim, nnod)    !    !     !                                                !
125
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
126
67
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
127
68
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
128
69
!  (ncelet, *)     !    !     !  (at current and preceding time steps)         !
134
75
! viscmx(ncelet)    ! ra ! <-- ! mesh viscosity in X direction                 !
135
76
! viscmy(ncelet)    ! ra ! <-- ! mesh viscosity in Y direction                 !
136
77
! viscmz(ncelet)    ! ra ! <-- ! mesh viscosity in Z direction                 !
137
 
! w1,2,3,4,5,6     ! ra ! --- ! work arrays                                    !
138
 
!  (ncelet)        !    !     !  (computation of pressure gradient)            !
139
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary developpement    !
140
 
! rtuser(nituse    ! ra ! <-- ! user-reserved real work array                  !
141
 
! ra(*)            ! ra ! --- ! main real work array                           !
142
78
!__________________!____!_____!________________________________________________!
143
79
 
144
80
!     Type: i (integer), r (real), s (string), a (array), l (logical),
146
82
!     mode: <-- input, --> output, <-> modifies data, --- work array
147
83
!===============================================================================
148
84
 
 
85
!===============================================================================
 
86
! Module files
 
87
!===============================================================================
 
88
 
 
89
use paramx
 
90
use dimens, only: ndimfb
 
91
use pointe
 
92
use numvar
 
93
use optcal
 
94
use cstphy
 
95
use entsor
 
96
use parall
 
97
use period
 
98
use albase
 
99
use mesh
 
100
 
 
101
!===============================================================================
 
102
 
149
103
implicit none
150
104
 
151
 
!===============================================================================
152
 
! Common blocks
153
 
!===============================================================================
154
 
 
155
 
include "dimfbr.h"
156
 
include "paramx.h"
157
 
include "pointe.h"
158
 
include "numvar.h"
159
 
include "optcal.h"
160
 
include "cstphy.h"
161
 
include "entsor.h"
162
 
include "parall.h"
163
 
include "period.h"
164
 
include "albase.h"
165
 
 
166
 
!===============================================================================
167
 
 
168
105
! Arguments
169
106
 
170
 
integer          idbia0 , idbra0
171
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
172
 
integer          nfml   , nprfml
173
 
integer          nnod   , lndfac , lndfbr , ncelbr
174
107
integer          nvar   , nscal
175
 
integer          nideve , nrdeve , nituse , nrtuse
176
 
 
177
 
integer          ifacel(2,nfac) , ifabor(nfabor)
178
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
179
 
integer          iprfml(nfml,nprfml)
180
 
integer          ipnfac(nfac+1), nodfac(lndfac)
181
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
182
 
integer          idevel(nideve), ituser(nituse)
183
 
integer          ia(*)
184
 
 
185
 
double precision xyzcen(ndim,ncelet)
186
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
187
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
188
 
double precision xyznod(ndim,nnod), volume(ncelet)
 
108
 
189
109
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
190
110
double precision propce(ncelet,*)
191
111
double precision propfa(nfac,*), propfb(ndimfb,*)
192
112
double precision coefa(ndimfb,*), coefb(ndimfb,*)
193
113
double precision viscmx(ncelet), viscmy(ncelet), viscmz(ncelet)
194
 
double precision w1(ncelet),w2(ncelet),w3(ncelet),w4(ncelet)
195
 
double precision w5(ncelet),w6(ncelet),w7(ncelet),w8(ncelet)
196
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
197
114
 
198
115
! Local variables
199
116
 
200
 
integer          idebia, idebra
201
117
integer          iel
202
118
double precision rad, xr2, xcen, ycen, zcen
203
119
 
211
127
!===============================================================================
212
128
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
213
129
 
214
 
idebia = idbia0
215
 
idebra = idbra0
216
130
 
217
131
!===============================================================================
218
132
!  1. Example :