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

« back to all changes in this revision

Viewing changes to src/alge/grdvni.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
!-------------------------------------------------------------------------------
 
2
 
 
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.
 
20
 
 
21
!-------------------------------------------------------------------------------
 
22
 
 
23
subroutine grdvni &
 
24
!================
 
25
 
 
26
 ( ivar   , imrgra , inc    , iccocg , nswrgp , imligp ,          &
 
27
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
 
28
   vel    , coefav , coefbv ,                                     &
 
29
   gradv  )
 
30
 
 
31
!===============================================================================
 
32
! FONCTION :
 
33
! ----------
 
34
 
 
35
! APPEL DES DIFFERENTES ROUTINES DE CALCUL DE GRADIENT CELLULE
 
36
 
 
37
!-------------------------------------------------------------------------------
 
38
! Arguments
 
39
!__________________.____._____.________________________________________________.
 
40
! name             !type!mode ! role                                           !
 
41
!__________________!____!_____!________________________________________________!
 
42
! ivar             ! e  ! <-- ! numero de la variable                          !
 
43
!                  !    !     !   destine a etre utilise pour la               !
 
44
!                  !    !     !   periodicite uniquement (pering)              !
 
45
!                  !    !     !   on pourra donner ivar=0 si la                !
 
46
!                  !    !     !   variable n'est ni une composante de          !
 
47
!                  !    !     !   la vitesse, ni une composante du             !
 
48
!                  !    !     !   tenseur des contraintes rij                  !
 
49
! imrgra           ! e  ! <-- ! methode de reconstruction du gradient          !
 
50
!                  !    !     !  0 reconstruction 97                           !
 
51
!                  !    !     !  1 moindres carres                             !
 
52
!                  !    !     !  2 moindres carres support etendu              !
 
53
!                  !    !     !    complet                                     !
 
54
!                  !    !     !  3 moindres carres avec selection du           !
 
55
!                  !    !     !    support etendu                              !
 
56
! inc              ! e  ! <-- ! indicateur = 0 resol sur increment             !
 
57
!                  !    !     !              1 sinon                           !
 
58
! iccocg           ! e  ! <-- ! indicateur = 1 pour recalcul de cocg           !
 
59
!                  !    !     !              0 sinon                           !
 
60
! nswrgp           ! e  ! <-- ! nombre de sweep pour reconstruction            !
 
61
!                  !    !     !             des gradients                      !
 
62
! imligp           ! e  ! <-- ! methode de limitation du gradient              !
 
63
!                  !    !     !  < 0 pas de limitation                         !
 
64
!                  !    !     !  = 0 a partir des gradients voisins            !
 
65
!                  !    !     !  = 1 a partir du gradient moyen                !
 
66
! iwarnp           ! i  ! <-- ! verbosity                                      !
 
67
! nfecra           ! e  ! <-- ! unite du fichier sortie std                    !
 
68
! epsrgp           ! r  ! <-- ! precision relative pour la                     !
 
69
!                  !    !     !  reconstruction des gradients 97               !
 
70
! climgp           ! r  ! <-- ! coef gradient*distance/ecart                   !
 
71
! extrap           ! r  ! <-- ! coef extrap gradient                           !
 
72
! vel(3,ncelet)    ! tr ! <-- ! variable (vitesse)                             !
 
73
! coefav,coefbv    ! tr ! <-- ! tableaux des cond lim pour pvar                !
 
74
!   (3,nfabor)     !    !     !  sur la normale a la face de bord              !
 
75
! gradv            ! tr ! --> ! gradient d'un vecteur                          !
 
76
!   (ncelet,3,3)   !    !     !                                                !
 
77
!__________________!____!_____!________________________________________________!
 
78
 
 
79
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
80
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
81
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
82
!            --- tableau de travail
 
83
!===============================================================================
 
84
 
 
85
!===============================================================================
 
86
! Module files
 
87
!===============================================================================
 
88
 
 
89
use paramx
 
90
use pointe
 
91
use parall
 
92
use period
 
93
use mesh
 
94
use cstphy
 
95
use cstnum
 
96
use albase
 
97
use cplsat
 
98
use dimens, only: ndimfb
 
99
 
 
100
!===============================================================================
 
101
 
 
102
implicit none
 
103
 
 
104
! Arguments
 
105
 
 
106
integer          ivar   , imrgra , inc    , iccocg , nswrgp
 
107
integer          imligp ,iwarnp  , nfecra
 
108
double precision epsrgp , climgp , extrap
 
109
 
 
110
double precision vel(3*ncelet)
 
111
double precision coefav(*), coefbv(*)
 
112
double precision gradv(3*3*ncelet)
 
113
 
 
114
! Local variables
 
115
 
 
116
integer          iel, isou, ivarloc
 
117
integer          iphydp
 
118
integer          idimte , itenso
 
119
integer          iiu,iiv,iiw
 
120
integer          iitytu
 
121
integer          iir11,iir22,iir33
 
122
integer          iir12,iir13,iir23
 
123
integer          imlini
 
124
 
 
125
double precision rvoid(1)
 
126
 
 
127
!===============================================================================
 
128
 
 
129
!===============================================================================
 
130
! 0. PREPARATION POUR PERIODICITE DE ROTATION
 
131
!===============================================================================
 
132
 
 
133
! Par defaut, on traitera le gradient comme un vecteur ...
 
134
!   (i.e. on suppose que c'est le gradient d'une grandeurs scalaire)
 
135
 
 
136
! S'il n'y a pas de rotation, les echanges d'informations seront
 
137
!   faits par percom (implicite)
 
138
 
 
139
! S'il y a une ou des periodicites de rotation,
 
140
!   on determine si la variables est un vecteur (vitesse)
 
141
!   ou un tenseur (de Reynolds)
 
142
!   pour lui appliquer dans percom le traitement adequat.
 
143
!   On positionne IDIMTE et ITENSO
 
144
!   et on recupere le gradient qui convient.
 
145
! Notons que si on n'a pas, auparavant, calcule et stocke les gradients
 
146
!   du halo on ne peut pas les recuperer ici (...).
 
147
!   Aussi ce sous programme est-il appele dans phyvar (dans perinu perinr)
 
148
!   pour calculer les gradients au debut du pas de temps et les stocker
 
149
!   dans DUDXYZ et DRDXYZ
 
150
 
 
151
! Il est necessaire que ITENSO soit toujours initialise, meme hors
 
152
!   periodicite, donc on l'initialise au prealable a sa valeur par defaut.
 
153
 
 
154
 
 
155
if(iperio.eq.1) then
 
156
 
 
157
  idimte = 1
 
158
  itenso = 0
 
159
 
 
160
  ! On recupere d'abord certains pointeurs necessaires a PERING
 
161
 
 
162
  call pergra                                                     &
 
163
  !==========
 
164
  ( iiu    , iiv    , iiw    ,                                    &
 
165
    iitytu ,                                                      &
 
166
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  )
 
167
 
 
168
  ivarloc = ivar
 
169
 
 
170
  call pering                                                     &
 
171
  !==========
 
172
  ( ivarloc,                                                      &
 
173
    idimte , itenso , iperot , iguper , igrper ,                  &
 
174
    iiu    , iiv    , iiw    , iitytu ,                           &
 
175
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  ,         &
 
176
    gradv(1), gradv(1+1*ncelet), gradv(1+2*ncelet),               &
 
177
    dudxy  , drdxy  )
 
178
 
 
179
  ivarloc = ivarloc + 1
 
180
 
 
181
  call pering                                                     &
 
182
  !==========
 
183
  ( ivarloc,                                                      &
 
184
    idimte , itenso , iperot , iguper , igrper ,                  &
 
185
    iiu    , iiv    , iiw    , iitytu ,                           &
 
186
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  ,         &
 
187
    gradv(1+3*ncelet), gradv(1+4*ncelet), gradv(1+5*ncelet),      &
 
188
    dudxy  , drdxy  )
 
189
 
 
190
  ivarloc = ivarloc + 1
 
191
 
 
192
  call pering                                                     &
 
193
  !==========
 
194
  ( ivarloc,                                                      &
 
195
    idimte , itenso , iperot , iguper , igrper ,                  &
 
196
    iiu    , iiv    , iiw    , iitytu ,                           &
 
197
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  ,         &
 
198
    gradv(1+6*ncelet), gradv(1+7*ncelet), gradv(1+8*ncelet),      &
 
199
    dudxy  , drdxy  )
 
200
 
 
201
endif
 
202
 
 
203
 
 
204
 
 
205
 
 
206
 
 
207
 
 
208
!===============================================================================
 
209
! 1. COMPUTATION OF THE GARDIENT
 
210
!===============================================================================
 
211
 
 
212
! This subroutine is never used to compute the pressure gradient
 
213
iphydp = 0
 
214
 
 
215
ivarloc = ivar
 
216
 
 
217
call cgdcel &
 
218
!==========
 
219
 ( ncelet , ncel   , nfac   , nfabor , ncelbr , ivarloc,          &
 
220
   imrgra , inc    , iccocg , nswrgp , idimte , itenso , iphydp , &
 
221
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
222
   ifacel , ifabor , icelbr , isympa ,                            &
 
223
   volume , surfac , surfbo , surfbn , pond,                      &
 
224
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
225
   rvoid  , rvoid  , rvoid  ,                                     &
 
226
   xyzcen , cdgfac , cdgfbo ,                                     &
 
227
   coefav(1)       , coefbv(1)       , vel(1) ,                   &
 
228
   cocgb  , cocg   ,                                              &
 
229
   cocib  , coci   ,                                              &
 
230
   gradv(1)     )
 
231
 
 
232
ivarloc = ivarloc+1
 
233
 
 
234
call cgdcel &
 
235
!==========
 
236
 ( ncelet , ncel   , nfac   , nfabor , ncelbr , ivarloc,          &
 
237
   imrgra , inc    , iccocg , nswrgp , idimte , itenso , iphydp , &
 
238
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
239
   ifacel , ifabor , icelbr , isympa ,                            &
 
240
   volume , surfac , surfbo , surfbn , pond,                      &
 
241
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
242
   rvoid  , rvoid  , rvoid  ,                                     &
 
243
   xyzcen , cdgfac , cdgfbo ,                                     &
 
244
   coefav(1+ndimfb), coefbv(1+ndimfb), vel(1+ncelet)   ,          &
 
245
   cocgb  , cocg   ,                                              &
 
246
   cocib  , coci   ,                                              &
 
247
   gradv(1+3*ncelet)     )
 
248
 
 
249
ivarloc = ivarloc+1
 
250
 
 
251
call cgdcel &
 
252
!==========
 
253
 ( ncelet , ncel   , nfac   , nfabor , ncelbr , ivarloc,          &
 
254
   imrgra , inc    , iccocg , nswrgp , idimte , itenso , iphydp , &
 
255
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
256
   ifacel , ifabor , icelbr , isympa ,                            &
 
257
   volume , surfac , surfbo , surfbn , pond,                      &
 
258
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
259
   rvoid  , rvoid  , rvoid  ,                                     &
 
260
   xyzcen , cdgfac , cdgfbo ,                                     &
 
261
   coefav(1+2*ndimfb), coefbv(1+2*ndimfb), vel(1+2*ncelet),       &
 
262
   cocgb  , cocg   ,                                              &
 
263
   cocib  , coci   ,                                              &
 
264
   gradv(1+6*ncelet)  )
 
265
 
 
266
 
 
267
return
 
268
end subroutine