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

« back to all changes in this revision

Viewing changes to src/alge/grdpot.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 grdpot &
 
24
!================
 
25
 
 
26
 ( ivar   , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
 
27
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
 
28
   ppond  ,                                                       &
 
29
   fextx  , fexty  , fextz  ,                                     &
 
30
   pvar   , coefap , coefbp ,                                     &
 
31
   grad   )
 
32
 
 
33
!===============================================================================
 
34
! FONCTION :
 
35
! ----------
 
36
 
 
37
! APPEL DES DIFFERENTES ROUTINES DE CALCUL DE GRADIENT CELLULE
 
38
 
 
39
!-------------------------------------------------------------------------------
 
40
! Arguments
 
41
!__________________.____._____.________________________________________________.
 
42
! name             !type!mode ! role                                           !
 
43
!__________________!____!_____!________________________________________________!
 
44
! ivar             ! e  ! <-- ! numero de la variable                          !
 
45
!                  !    !     !   destine a etre utilise pour la               !
 
46
!                  !    !     !   periodicite uniquement (pering)              !
 
47
!                  !    !     !   on pourra donner ivar=0 si la                !
 
48
!                  !    !     !   variable n'est ni une composante de          !
 
49
!                  !    !     !   la vitesse, ni une composante du             !
 
50
!                  !    !     !   tenseur des contraintes rij                  !
 
51
! imrgra           ! e  ! <-- ! methode de reconstruction du gradient          !
 
52
!                  !    !     !  0 reconstruction 97                           !
 
53
!                  !    !     !  1 moindres carres                             !
 
54
!                  !    !     !  2 moindres carres support etendu              !
 
55
!                  !    !     !    complet                                     !
 
56
!                  !    !     !  3 moindres carres avec selection du           !
 
57
!                  !    !     !    support etendu                              !
 
58
! inc              ! e  ! <-- ! indicateur = 0 resol sur increment             !
 
59
!                  !    !     !              1 sinon                           !
 
60
! iccocg           ! e  ! <-- ! indicateur = 1 pour recalcul de cocg           !
 
61
!                  !    !     !              0 sinon                           !
 
62
! nswrgp           ! e  ! <-- ! nombre de sweep pour reconstruction            !
 
63
!                  !    !     !             des gradients                      !
 
64
! imligp           ! e  ! <-- ! methode de limitation du gradient              !
 
65
!                  !    !     !  < 0 pas de limitation                         !
 
66
!                  !    !     !  = 0 a partir des gradients voisins            !
 
67
!                  !    !     !  = 1 a partir du gradient moyen                !
 
68
! iwarnp           ! i  ! <-- ! verbosity                                      !
 
69
! iphydp           ! e  ! <-- ! indicateur de prise en compte de la            !
 
70
!                  !    !     ! pression hydrostatique                         !
 
71
! nfecra           ! e  ! <-- ! unite du fichier sortie std                    !
 
72
! epsrgp           ! r  ! <-- ! precision relative pour la                     !
 
73
!                  !    !     !  reconstruction des gradients 97               !
 
74
! climgp           ! r  ! <-- ! coef gradient*distance/ecart                   !
 
75
! extrap           ! r  ! <-- ! coef extrap gradient                           !
 
76
! pvar  (ncelet    ! tr ! <-- ! variable (pression)                            !
 
77
! coefap,coefbp    ! tr ! <-- ! tableaux des cond lim pour pvar                !
 
78
!   (nfabor)       !    !     !  sur la normale a la face de bord              !
 
79
! ppond(ncelet)    ! tr ! <-- ! ponderation "physique"                         !
 
80
! fextx,y,z        ! tr ! <-- ! force exterieure generant la pression          !
 
81
!   (ncelet)       !    !     !  hydrostatique                                 !
 
82
! grad(ncelet,3)   ! tr ! --> ! gradient de pvar                               !
 
83
!__________________!____!_____!________________________________________________!
 
84
 
 
85
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
86
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
87
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
88
!            --- tableau de travail
 
89
!===============================================================================
 
90
 
 
91
!===============================================================================
 
92
! Module files
 
93
!===============================================================================
 
94
 
 
95
use paramx
 
96
use pointe
 
97
use parall
 
98
use period
 
99
use mesh
 
100
 
 
101
!===============================================================================
 
102
 
 
103
implicit none
 
104
 
 
105
! Arguments
 
106
 
 
107
integer          ivar   , imrgra , inc    , iccocg , nswrgp
 
108
integer          imligp ,iwarnp  , iphydp , nfecra
 
109
double precision epsrgp , climgp , extrap
 
110
 
 
111
 
 
112
double precision ppond(ncelet)
 
113
double precision fextx(ncelet),fexty(ncelet),fextz(ncelet)
 
114
double precision pvar(ncelet), coefap(nfabor), coefbp(nfabor)
 
115
double precision grad(ncelet,3)
 
116
 
 
117
! Local variables
 
118
 
 
119
integer          idimte , itenso
 
120
integer          iiu,iiv,iiw
 
121
integer          iitytu
 
122
integer          iir11,iir22,iir33
 
123
integer          iir12,iir13,iir23
 
124
integer          imlini
 
125
 
 
126
double precision climin
 
127
 
 
128
!===============================================================================
 
129
 
 
130
!===============================================================================
 
131
! 0. INITIALISATION
 
132
!===============================================================================
 
133
 
 
134
! The gradient of a potential (pressure, ...) is a vector
 
135
 
 
136
idimte = 1
 
137
itenso = 0
 
138
 
 
139
!===============================================================================
 
140
! 1. CALCUL DU GRADIENT
 
141
!===============================================================================
 
142
 
 
143
 
 
144
call cgdcel                                                       &
 
145
!==========
 
146
 ( ncelet , ncel   , nfac   , nfabor , ncelbr , ivar   ,          &
 
147
   imrgra , inc    , iccocg , nswrgp , idimte , itenso , iphydp , &
 
148
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
149
   ifacel , ifabor , icelbr , isympa ,                            &
 
150
   volume , surfac , surfbo , surfbn , pond,                      &
 
151
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
152
   fextx  , fexty  , fextz  ,                                     &
 
153
   xyzcen , cdgfac , cdgfbo, coefap , coefbp , pvar   ,           &
 
154
   cocgb  , cocg   ,                                              &
 
155
   cocib  , coci   ,                                              &
 
156
   grad   )
 
157
 
 
158
return
 
159
end subroutine