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

« back to all changes in this revision

Viewing changes to src/alge/grdcel.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 grdcel &
 
24
!================
 
25
 
 
26
 ( ivar   , imrgra , inc    , iccocg , nswrgp , imligp ,          &
 
27
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
 
28
   pvar   , coefap , coefbp ,                                     &
 
29
   grad   )
 
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
! pvar  (ncelet    ! tr ! <-- ! variable (pression)                            !
 
73
! coefap,coefbp    ! tr ! <-- ! tableaux des cond lim pour pvar                !
 
74
!   (nfabor)       !    !     !  sur la normale a la face de bord              !
 
75
! grad(ncelet,3)   ! tr ! --> ! gradient de pvar                               !
 
76
!__________________!____!_____!________________________________________________!
 
77
 
 
78
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
79
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
80
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
81
!            --- tableau de travail
 
82
!===============================================================================
 
83
 
 
84
!===============================================================================
 
85
! Module files
 
86
!===============================================================================
 
87
 
 
88
use paramx
 
89
use pointe
 
90
use parall
 
91
use period
 
92
use mesh
 
93
 
 
94
!===============================================================================
 
95
 
 
96
implicit none
 
97
 
 
98
! Arguments
 
99
 
 
100
integer          ivar   , imrgra , inc    , iccocg , nswrgp
 
101
integer          imligp ,iwarnp  , nfecra
 
102
double precision epsrgp , climgp , extrap
 
103
 
 
104
 
 
105
double precision pvar(ncelet), coefap(nfabor), coefbp(nfabor)
 
106
double precision grad(ncelet,3)
 
107
 
 
108
! Local variables
 
109
 
 
110
integer          iphydp
 
111
integer          idimte , itenso
 
112
integer          iiu,iiv,iiw
 
113
integer          iitytu
 
114
integer          iir11,iir22,iir33
 
115
integer          iir12,iir13,iir23
 
116
integer          imlini
 
117
 
 
118
double precision rvoid(1)
 
119
double precision climin
 
120
 
 
121
!===============================================================================
 
122
 
 
123
!===============================================================================
 
124
! 0. PREPARATION POUR PERIODICITE DE ROTATION
 
125
!===============================================================================
 
126
 
 
127
! Par defaut, on traitera le gradient comme un vecteur ...
 
128
!   (i.e. on suppose que c'est le gradient d'une grandeurs scalaire)
 
129
 
 
130
! S'il n'y a pas de rotation, les echanges d'informations seront
 
131
!   faits par percom (implicite)
 
132
 
 
133
! S'il y a une ou des periodicites de rotation,
 
134
!   on determine si la variables est un vecteur (vitesse)
 
135
!   ou un tenseur (de Reynolds)
 
136
!   pour lui appliquer dans percom le traitement adequat.
 
137
!   On positionne IDIMTE et ITENSO
 
138
!   et on recupere le gradient qui convient.
 
139
! Notons que si on n'a pas, auparavant, calcule et stocke les gradients
 
140
!   du halo on ne peut pas les recuperer ici (...).
 
141
!   Aussi ce sous programme est-il appele dans phyvar (dans perinu perinr)
 
142
!   pour calculer les gradients au debut du pas de temps et les stocker
 
143
!   dans DUDXYZ et DRDXYZ
 
144
 
 
145
! Il est necessaire que ITENSO soit toujours initialise, meme hors
 
146
!   periodicite, donc on l'initialise au prealable a sa valeur par defaut.
 
147
 
 
148
idimte = 1
 
149
itenso = 0
 
150
 
 
151
if(iperio.eq.1) then
 
152
 
 
153
!       On recupere d'abord certains pointeurs necessaires a PERING
 
154
 
 
155
    call pergra                                                   &
 
156
    !==========
 
157
  ( iiu    , iiv    , iiw    ,                                    &
 
158
    iitytu ,                                                      &
 
159
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  )
 
160
 
 
161
  call pering                                                     &
 
162
  !==========
 
163
  ( ivar   ,                                                      &
 
164
    idimte , itenso , iperot , iguper , igrper ,                  &
 
165
    iiu    , iiv    , iiw    , iitytu ,                           &
 
166
    iir11  , iir22  , iir33  , iir12  , iir13  , iir23  ,         &
 
167
    grad(1,1) , grad(1,2) , grad(1,3) ,                           &
 
168
    dudxy  , drdxy  )
 
169
endif
 
170
 
 
171
!===============================================================================
 
172
! 1. CALCUL DU GRADIENT
 
173
!===============================================================================
 
174
 
 
175
! This subroutine is never used to compute the pressure gradient
 
176
iphydp = 0
 
177
 
 
178
call cgdcel                                                       &
 
179
!==========
 
180
 ( ncelet , ncel   , nfac   , nfabor , ncelbr , ivar   ,          &
 
181
   imrgra , inc    , iccocg , nswrgp , idimte , itenso , iphydp , &
 
182
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
183
   ifacel , ifabor , icelbr , isympa ,                            &
 
184
   volume , surfac , surfbo , surfbn , pond,                      &
 
185
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
186
   rvoid  , rvoid  , rvoid  ,                                     &
 
187
   xyzcen , cdgfac , cdgfbo, coefap , coefbp , pvar   ,           &
 
188
   cocgb  , cocg   ,                                              &
 
189
   cocib  , coci   ,                                              &
 
190
   grad   )
 
191
 
 
192
return
 
193
end subroutine