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

« back to all changes in this revision

Viewing changes to src/base/calgeo.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 the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
25
 
 
26
 
!-------------------------------------------------------------------------------
27
 
 
28
 
subroutine calgeo &
29
 
!================
30
 
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndfac , lndfbr ,                                     &
34
 
   nideve , nrdeve , nituse , nrtuse ,                            &
35
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
36
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
37
 
   idevel , ituser , ia     ,                                     &
38
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
39
 
   volmin , volmax , voltot ,                                     &
40
 
   rdevel , rtuser , ra     )
41
 
 
42
 
!===============================================================================
43
 
!  FONCTION  :
44
 
!  ---------
45
 
 
46
 
!  CALCUL DES ENTITES GEOMETRIQUES DEDUITES
47
 
!     DU JEU DE DONNEES MINIMAL
48
 
 
49
 
!-------------------------------------------------------------------------------
50
 
! Arguments
51
 
!__________________.____._____.________________________________________________.
52
 
! name             !type!mode ! role                                           !
53
 
!__________________!____!_____!________________________________________________!
54
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
55
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
56
 
! ndim             ! i  ! <-- ! spatial dimension                              !
57
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
58
 
! ncel             ! i  ! <-- ! number of cells                                !
59
 
! nfac             ! i  ! <-- ! number of interior faces                       !
60
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
61
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
62
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
63
 
! nnod             ! i  ! <-- ! number of vertices                             !
64
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
65
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
66
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
67
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
68
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
69
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
70
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
71
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
72
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
73
 
!  (nfml, nprfml)  !    !     !                                                !
74
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
75
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
76
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
77
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
78
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
79
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
80
 
! ia(*)            ! ia ! --- ! main integer work array                        !
81
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
82
 
!  (ndim, ncelet)  !    !     !                                                !
83
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
84
 
!  (ndim, nfac)    !    !     !                                                !
85
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
86
 
!  (ndim, nfabor)  !    !     !                                                !
87
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
88
 
!  (ndim, nfac)    !    !     !                                                !
89
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
90
 
!  (ndim, nfabor)  !    !     !                                                !
91
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
92
 
!  (ndim, nnod)    !    !     !                                                !
93
 
! volume           ! tr ! --> ! volume d'un des ncelet elements                !
94
 
! (ncelet          !    !     !                                                !
95
 
! volmin           ! r  ! --> ! volume de controle minimal                     !
96
 
! volmax           ! r  ! --> ! volume de controle maximal                     !
97
 
! voltot           ! r  ! --> ! volume total du domaine                        !
98
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
99
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
100
 
! ra(*)            ! ra ! --- ! main real work array                           !
101
 
!__________________!____!_____!________________________________________________!
102
 
 
103
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
104
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
105
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
106
 
!            --- tableau de travail
107
 
!===============================================================================
108
 
 
109
 
implicit none
110
 
 
111
 
!===============================================================================
112
 
! Common blocks
113
 
!===============================================================================
114
 
 
115
 
include "paramx.h"
116
 
include "optcal.h"
117
 
include "pointe.h"
118
 
 
119
 
!===============================================================================
120
 
 
121
 
! Arguments
122
 
 
123
 
integer          idbia0 , idbra0
124
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
125
 
integer          nfml   , nprfml
126
 
integer          nnod   , lndfac , lndfbr
127
 
integer          nideve , nrdeve , nituse , nrtuse
128
 
 
129
 
integer          ifacel(2,nfac) , ifabor(nfabor)
130
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
131
 
integer          iprfml(nfml,nprfml)
132
 
integer          ipnfac(nfac+1), nodfac(lndfac)
133
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
134
 
integer          idevel(nideve), ituser(nituse), ia(*)
135
 
 
136
 
double precision xyzcen(ndim,ncelet)
137
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
138
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
139
 
double precision xyznod(ndim,nnod), volume(ncelet)
140
 
double precision volmin, volmax, voltot
141
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
142
 
 
143
 
! Local variables
144
 
 
145
 
integer idebia, idebra
146
 
 
147
 
!===============================================================================
148
 
! 1. ON SAUVEGARDE LA POSITION DE LA MEMOIRE
149
 
!===============================================================================
150
 
 
151
 
idebia = idbia0
152
 
idebra = idbra0
153
 
 
154
 
!===============================================================================
155
 
! 2. ON CALCULE LE VOLUME MIN et TOTAL DES ELEMENTS
156
 
!===============================================================================
157
 
 
158
 
call clvolc                                                       &
159
 
!==========
160
 
     ( ncelet , ncel   ,                                          &
161
 
       volmin , volmax , voltot , volume )
162
 
 
163
 
!===============================================================================
164
 
! 3. ON CALCULE LES SURFACES DES FACES
165
 
!===============================================================================
166
 
 
167
 
call clsurn                                                       &
168
 
!==========
169
 
     ( idebia , idebra ,                                          &
170
 
       nfac   , nfabor ,                                          &
171
 
       surfac , surfbo ,                                          &
172
 
       ra(isrfan) , ra(isrfbn) ,                                  &
173
 
       ia     , ra     )
174
 
 
175
 
 
176
 
!===============================================================================
177
 
! 4. ON CALCULE LE PRODUIT SCALAIRE DE LA NORMALE NORMEE A UNE FACE ET
178
 
!        DU VECTEUR DEFINI PAR LES VOISINS (VOISIN 1 : ORIGINE,
179
 
!        VOISIN 2 : EXTREMITE)
180
 
!               LA PONDERATION RESULTANTE   POND  = D2/(D1+D2)
181
 
!        OU D1 ET D2 SONT LES PROJETES SUR LA NORMALE A LA FACE DES
182
 
!        VECTEURS DEFINIS RESPECTIVEMENT PAR
183
 
!    D1 : (ORIGINE : VOISIN 1, EXTREMITE : CENTRE DE GRAVITE DE LA FACE)
184
 
!    D2 : (ORIGINE : CENTRE DE GRAVITE DE LA FACE, EXTREMITE : VOISIN 2)
185
 
!===============================================================================
186
 
 
187
 
call cldipo                                                       &
188
 
!==========
189
 
 ( idebia , idebra ,                                              &
190
 
   nfac   , nfabor , ncelet , ncel   ,                            &
191
 
   ifacel , ifabor ,                                              &
192
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo ,                   &
193
 
   ra(isrfan) , ra(isrfbn) ,                                      &
194
 
   ra(idist)  , ra(idistb) , ra(ipond) ,                          &
195
 
   ia     , ra     )
196
 
 
197
 
!===============================================================================
198
 
! 5. ON CALCULE LES VECTEURS IIP ET JJP POUR LES RECONSTRUCTIONS
199
 
!===============================================================================
200
 
 
201
 
call cldijp                                                       &
202
 
!==========
203
 
 ( idebia , idebra ,                                              &
204
 
   nfac   , nfabor , ncelet , ncel   ,                            &
205
 
   ifacel , ifabor ,                                              &
206
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo ,                   &
207
 
   ra(isrfan) , ra(isrfbn) ,                                      &
208
 
   ra(ipond)  ,                                                   &
209
 
   ra(idijpf) , ra(idiipb)  , ra(idofij) ,                        &
210
 
   ia     , ra     )
211
 
 
212
 
 
213
 
!===============================================================================
214
 
! 6. FILTRAGE DU VOISINAGE ETENDU POUR LE GRADIENT PAR MOINDRES CARRES
215
 
!===============================================================================
216
 
 
217
 
if (imrgra.eq.3) then
218
 
 
219
 
  call redvse (anomax)
220
 
  !==========
221
 
 
222
 
endif
223
 
 
224
 
 
225
 
!===============================================================================
226
 
! 8. FIN
227
 
!===============================================================================
228
 
 
229
 
 
230
 
return
231
 
end subroutine