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

« back to all changes in this revision

Viewing changes to src/alge/grdvec.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 grdvec &
 
24
!================
 
25
 
 
26
 ( ivar   , imrgra , inc    , iccocg , nswrgp , imligp ,          &
 
27
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
 
28
   ilved  ,                                                       &
 
29
   pvar   , coefav , coefbv ,                                     &
 
30
   gradv )
 
31
 
 
32
!===============================================================================
 
33
! FONCTION :
 
34
! ----------
 
35
 
 
36
! APPEL DES DIFFERENTES ROUTINES DE CALCUL DE GRADIENT CELLULE
 
37
 
 
38
!-------------------------------------------------------------------------------
 
39
! Arguments
 
40
!__________________.____._____.________________________________________________.
 
41
! name             !type!mode ! role                                           !
 
42
!__________________!____!_____!________________________________________________!
 
43
! ivar             ! e  ! <-- ! numero de la variable                          !
 
44
!                  !    !     !   destine a etre utilise pour la               !
 
45
!                  !    !     !   periodicite uniquement (pering)              !
 
46
!                  !    !     !   on pourra donner ivar=0 si la                !
 
47
!                  !    !     !   variable n'est ni une composante de          !
 
48
!                  !    !     !   la vitesse, ni une composante du             !
 
49
!                  !    !     !   tenseur des contraintes rij                  !
 
50
! imrgra           ! e  ! <-- ! methode de reconstruction du gradient          !
 
51
!                  !    !     !  0 reconstruction 97                           !
 
52
!                  !    !     !  1 moindres carres                             !
 
53
!                  !    !     !  2 moindres carres support etendu              !
 
54
!                  !    !     !    complet                                     !
 
55
!                  !    !     !  3 moindres carres avec selection du           !
 
56
!                  !    !     !    support etendu                              !
 
57
! inc              ! e  ! <-- ! indicateur = 0 resol sur increment             !
 
58
!                  !    !     !              1 sinon                           !
 
59
! iccocg           ! e  ! <-- ! indicateur = 1 pour recalcul de cocg           !
 
60
!                  !    !     !              0 sinon                           !
 
61
! nswrgp           ! e  ! <-- ! nombre de sweep pour reconstruction            !
 
62
!                  !    !     !             des gradients                      !
 
63
! imligp           ! e  ! <-- ! methode de limitation du gradient              !
 
64
!                  !    !     !  < 0 pas de limitation                         !
 
65
!                  !    !     !  = 0 a partir des gradients voisins            !
 
66
!                  !    !     !  = 1 a partir du gradient moyen                !
 
67
! iwarnp           ! i  ! <-- ! verbosity                                      !
 
68
! nfecra           ! e  ! <-- ! unite du fichier sortie std                    !
 
69
! epsrgp           ! r  ! <-- ! precision relative pour la                     !
 
70
!                  !    !     !  reconstruction des gradients 97               !
 
71
! climgp           ! r  ! <-- ! coef gradient*distance/ecart                   !
 
72
! extrap           ! r  ! <-- ! coef extrap gradient                           !
 
73
! pvar(3,ncelet)   ! tr ! <-- ! variable (vectorielle)                         !
 
74
! coefav,coefbv    ! tr ! <-- ! tableaux des cond lim pour pvar                !
 
75
!   (3,nfabor)     !    !     !  sur la normale a la face de bord              !
 
76
! gradv            ! tr ! --> ! gradient de la variable vectorielle            !
 
77
!   (3,3,ncelet)   !    !     !                                                !
 
78
!__________________!____!_____!________________________________________________!
 
79
 
 
80
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
81
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
82
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
83
!            --- tableau de travail
 
84
!===============================================================================
 
85
 
 
86
!===============================================================================
 
87
! Module files
 
88
!===============================================================================
 
89
 
 
90
use paramx
 
91
use pointe
 
92
use parall
 
93
use period
 
94
use mesh
 
95
use cstphy
 
96
use cstnum
 
97
use albase
 
98
use cplsat
 
99
use dimens, only: ndimfb
 
100
 
 
101
!===============================================================================
 
102
 
 
103
implicit none
 
104
 
 
105
! Arguments
 
106
 
 
107
integer          ivar   , imrgra , inc    , iccocg , nswrgp
 
108
integer          imligp ,iwarnp  , nfecra
 
109
double precision epsrgp , climgp , extrap
 
110
 
 
111
double precision pvar(*)
 
112
double precision coefav(*), coefbv(*)
 
113
double precision gradv(*)
 
114
 
 
115
logical ilved
 
116
 
 
117
! Local variables
 
118
 
 
119
integer          iel, isou, jsou
 
120
 
 
121
double precision, dimension(:,:), allocatable :: pvari
 
122
double precision, dimension(:,:,:), allocatable :: gradvi
 
123
 
 
124
!===============================================================================
 
125
 
 
126
!===============================================================================
 
127
! 1. COMPUTATION OF THE GARDIENT
 
128
!===============================================================================
 
129
 
 
130
! the velocity and the gradient fields are interleaved
 
131
if (ilved) then
 
132
 
 
133
  call cgdvec                                                     &
 
134
  !==========
 
135
 ( ncelet , ncel   , nfac   , nfabor , ivar   ,                   &
 
136
   imrgra , inc    , nswrgp ,                                     &
 
137
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
138
   ifacel , ifabor , isympa ,                                     &
 
139
   volume , surfac , surfbo , surfbn , pond   ,                   &
 
140
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
141
   xyzcen , cdgfac , cdgfbo , coefav , coefbv , pvar   ,          &
 
142
   cocgu  ,                                                       &
 
143
   gradv  )
 
144
 
 
145
! We interleave the velocity
 
146
else
 
147
 
 
148
  !Allocation
 
149
  allocate(pvari(3,ncelet))
 
150
  allocate(gradvi(3,3,ncelet))
 
151
 
 
152
  do isou = 1, 3
 
153
    do iel = 1, ncelet
 
154
      pvari(isou,iel) = pvar(iel + (isou-1)*ncelet)
 
155
    enddo
 
156
  enddo
 
157
 
 
158
  call cgdvec                                                     &
 
159
  !==========
 
160
 ( ncelet , ncel   , nfac   , nfabor , ivar   ,                   &
 
161
   imrgra , inc    , nswrgp ,                                     &
 
162
   iwarnp , nfecra , imligp , epsrgp , extrap , climgp ,          &
 
163
   ifacel , ifabor , isympa ,                                     &
 
164
   volume , surfac , surfbo , surfbn , pond   ,                   &
 
165
   dist   , distb  , dijpf  , diipb  , dofij  ,                   &
 
166
   xyzcen , cdgfac , cdgfbo , coefav , coefbv , pvari  ,          &
 
167
   cocgu  ,                                                       &
 
168
   gradvi )
 
169
 
 
170
 
 
171
  do isou = 1, 3
 
172
    do jsou = 1, 3
 
173
      do iel = 1, ncelet
 
174
        gradv(iel + (jsou-1)*ncelet + (isou-1)*3*ncelet) = gradvi(isou,jsou,iel)
 
175
      enddo
 
176
    enddo
 
177
  enddo
 
178
 
 
179
  ! Free memory
 
180
  deallocate(pvari, gradvi)
 
181
 
 
182
endif
 
183
 
 
184
return
 
185
end subroutine