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

« back to all changes in this revision

Viewing changes to src/base/cldijp.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 cldijp &
29
 
!================
30
 
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   nfac   , nfabor , ncelet , ncel   ,                            &
33
 
   ifacel , ifabor ,                                              &
34
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo ,                   &
35
 
   surfan , surfbn ,                                              &
36
 
   pond   ,                                                       &
37
 
   dijpf  , diipb  , dofij  ,                                     &
38
 
   ia     , ra     )
39
 
 
40
 
!===============================================================================
41
 
 
42
 
!  FONCTION  :
43
 
!  --------
44
 
 
45
 
!    CALCUL DE VECTEURS POUR TERMES DE NON ORTHOGONALITE :
46
 
 
47
 
!       SOIT UNE FACE A,B,C ET I,J LES CENTRES DES VOLUMES VOISINS.
48
 
!         (SEUL I EST DEFINI POUR UNE FACE DE BORD)
49
 
 
50
 
!       LA FACE EST ORIENTEE DE I VERS J, DE NORMALE NIJ.
51
 
!         (LES FACES DE BORD SONT ORIENTEES VERS L'EXTERIEUR)
52
 
!       LA NORME DE NIJ VAUT 1.
53
 
!       SIJ EST LA SURFACE DE LA FACE ABC.
54
 
!       ON DEFINIT I' ET J' LES PROJETES ORTHOGONAUX DE
55
 
!         I ET J SUR LA DROITE ORTHOGONALE A ABC PASSANT PAR SON CDG F
56
 
!         (SEUL I' EST DEFINI POUR LES FACES DE BORD)
57
 
 
58
 
!       ON CALCULE ICI LE VECTEUR I'J' AUX FACES INTERNES (DIJPF)
59
 
!                      LE VECTEUR II'  AUX FACES DE BORD  (DIIPB)
60
 
!                      LE VECTEUR OF   AUX FACES INTERNES (DOFIJ)
61
 
 
62
 
!       NOTER LES RELATIONS
63
 
!                 II' = IG - (IG.NIJ)NIJ
64
 
!                 JJ' = JG - (JG.NIJ)NIJ
65
 
 
66
 
!-------------------------------------------------------------------------------
67
 
! Arguments
68
 
!__________________.____._____.________________________________________________.
69
 
! name             !type!mode ! role                                           !
70
 
!__________________!____!_____!________________________________________________!
71
 
! idbia0/idbra0    ! e  ! <-- ! pointeur de la premiere cas libre des          !
72
 
!                  !    !     !  tableaux ia/ra                                !
73
 
! nfac             ! e  ! <-- ! nombre total de faces internes                 !
74
 
! nfabor           ! e  ! <-- ! nombre total de faces         de bord          !
75
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
76
 
! ncel             ! i  ! <-- ! number of cells                                !
77
 
! ifacel           ! te ! <-- ! ifacel(iel,ifac) num glob de l'elemnt          !
78
 
! (2,nfac)         !    !     !  vois iel (1 ou 2) de la fac int ifac          !
79
 
! ifabor           ! te ! <-- ! ifabor(ifac    ) num glob de l'elt             !
80
 
! nfabor  )        !    !     !  voisin iel (1) de la fac de brd ifac          !
81
 
! xyzcen           ! tr ! <-- ! coords du "centre" des nelem elements          !
82
 
! (3,ncelet        !    !     !                                                !
83
 
! surfac           ! tr ! <-- ! coords du vecteur surface des nfac             !
84
 
! (3,nfac  )       !    !     ! faces internes; dirige du vois 1 vers          !
85
 
!                  !    !     !  le vois 2 (ifacel) ; non unitaire             !
86
 
! surfbo           ! tr ! <-- ! coords du vecteur surface des nfabor           !
87
 
! (3,nfabor)       !    !     !  faces de bord ; dirige vers                   !
88
 
!                  !    !     !  l'exterieur du domaine; non unitaire          !
89
 
! surfan           ! tr ! <-- ! norme de surfac (surface des faces             !
90
 
! (nfac    )       !    !     ! internes)                                      !
91
 
! surfbn           ! tr ! <-- ! norme de surfbo (surface des faces             !
92
 
! (nfabor  )       !    !     !  de bord)                                      !
93
 
! cdgfac           ! tr ! <-- ! coords du centre de gravite des faces          !
94
 
! 3,nfac  )        !    !     !           internes                             !
95
 
! cdgfbo           ! tr ! <-- ! coords du centre de gravite des faces          !
96
 
! 3,nfabor)        !    !     !           de  bord                             !
97
 
! pond             ! tr ! --> ! ponderation pour face interne                  !
98
 
! (nfac  )         !    !     !  = d2/(d1+d2) ou d1 et d2 sont les             !
99
 
!                  !    !     !  projetes sur la normale a la face             !
100
 
!                  !    !     !  des vecteurs definis resp. par :              !
101
 
!                  !    !     !d1(orig: voisin 1, extremite: cdg face          !
102
 
!                  !    !     !d2(orig: cdg face, extremite: voisin 2          !
103
 
! dijpf            ! tr ! --> ! vecteur i'j' pour les faces internes           !
104
 
! (ndim,nfac  )    !    !     !                                                !
105
 
! diipb            ! tr ! --> ! vecteur ii' pour les faces de bord             !
106
 
! (ndim,nfabor)    !    !     !                                                !
107
 
! dofij            ! tr ! --> ! vecteur of pour les faces internes             !
108
 
! (ndim,nfac  )    !    !     ! o : intersection de ij et la face              !
109
 
!                  !    !     ! f : centre de la face                          !
110
 
! ia               ! te ! --- ! tableau de travail entier                      !
111
 
! ra               ! tr ! --- ! tableau de travail reel                        !
112
 
!__________________.____._____.________________________________________________.
113
 
 
114
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
115
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
116
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
117
 
!            --- tableau de travail
118
 
!===============================================================================
119
 
 
120
 
implicit none
121
 
 
122
 
!===============================================================================
123
 
! Common blocks
124
 
!===============================================================================
125
 
 
126
 
!===============================================================================
127
 
 
128
 
! Arguments
129
 
 
130
 
integer idbia0,idbra0
131
 
integer nfac,nfabor,ncelet,ncel
132
 
integer ifacel(2,nfac)
133
 
integer ifabor(nfabor)
134
 
integer ia(*)
135
 
double precision xyzcen(3,ncelet)
136
 
double precision surfac(3,nfac),surfbo(3,nfabor)
137
 
double precision surfan(nfac),surfbn(nfabor)
138
 
double precision cdgfac(3,nfac),cdgfbo(3,nfabor)
139
 
double precision pond(nfac)
140
 
double precision dijpf(3,nfac)
141
 
double precision diipb(3,nfabor)
142
 
double precision dofij(3,nfac)
143
 
double precision ra(*)
144
 
 
145
 
integer ifac,ivois1,ivois2
146
 
double precision surfnx,surfny,surfnz
147
 
double precision vecigx,vecigy,vecigz
148
 
double precision vecijx,vecijy,vecijz
149
 
double precision dipjp
150
 
double precision psi
151
 
 
152
 
!===============================================================================
153
 
! 1. FACES INTERNES
154
 
!===============================================================================
155
 
 
156
 
do ifac = 1, nfac
157
 
 
158
 
!--->  NUMERO DES VOISINS
159
 
 
160
 
   ivois1 = ifacel(1,ifac)
161
 
   ivois2 = ifacel(2,ifac)
162
 
 
163
 
!---> NORMALE NORMEE
164
 
 
165
 
   surfnx = surfac(1,ifac)/surfan(ifac)
166
 
   surfny = surfac(2,ifac)/surfan(ifac)
167
 
   surfnz = surfac(3,ifac)/surfan(ifac)
168
 
 
169
 
!---> IJ
170
 
 
171
 
   vecijx = xyzcen(1,ivois2)-xyzcen(1,ivois1)
172
 
   vecijy = xyzcen(2,ivois2)-xyzcen(2,ivois1)
173
 
   vecijz = xyzcen(3,ivois2)-xyzcen(3,ivois1)
174
 
 
175
 
!---> DIJPP = IJ.NIJ
176
 
 
177
 
   dipjp  = vecijx*surfnx + vecijy*surfny +                       &
178
 
            vecijz*surfnz
179
 
 
180
 
!---> DIJPF = (IJ.NIJ).NIJ
181
 
 
182
 
   dijpf(1,ifac) = dipjp * surfnx
183
 
   dijpf(2,ifac) = dipjp * surfny
184
 
   dijpf(3,ifac) = dipjp * surfnz
185
 
 
186
 
!---> DOFIJ = OF
187
 
 
188
 
  dofij(1,ifac) = cdgfac(1,ifac) -                                &
189
 
                  (pond(ifac) * xyzcen(1,ivois1) +                &
190
 
                  (1.d0-pond(ifac))*xyzcen(1,ivois2))
191
 
  dofij(2,ifac) = cdgfac(2,ifac) -                                &
192
 
                  (pond(ifac)*xyzcen(2,ivois1) +                  &
193
 
                  (1.d0-pond(ifac))*xyzcen(2,ivois2))
194
 
  dofij(3,ifac) = cdgfac(3,ifac) -                                &
195
 
                  (pond(ifac)*xyzcen(3,ivois1) +                  &
196
 
                  (1.d0-pond(ifac))*xyzcen(3,ivois2))
197
 
 
198
 
enddo
199
 
 
200
 
!===============================================================================
201
 
! 2. FACES DE BORD
202
 
!===============================================================================
203
 
 
204
 
do ifac = 1, nfabor
205
 
 
206
 
!--->  NUMERO DU VOISIN
207
 
 
208
 
   ivois1 = ifabor(ifac)
209
 
 
210
 
!---> NORMALE NORMEE
211
 
 
212
 
   surfnx = surfbo(1,ifac)/surfbn(ifac)
213
 
   surfny = surfbo(2,ifac)/surfbn(ifac)
214
 
   surfnz = surfbo(3,ifac)/surfbn(ifac)
215
 
 
216
 
!---> IG
217
 
 
218
 
   vecigx = cdgfbo(1,ifac)-xyzcen(1,ivois1)
219
 
   vecigy = cdgfbo(2,ifac)-xyzcen(2,ivois1)
220
 
   vecigz = cdgfbo(3,ifac)-xyzcen(3,ivois1)
221
 
 
222
 
!---> PSI = IG.NIJ
223
 
 
224
 
   psi = vecigx*surfnx+vecigy*surfny+vecigz*surfnz
225
 
 
226
 
!---> DIIPB = IG - (IG.NIJ)NIJ
227
 
 
228
 
   diipb(1,ifac) = vecigx - psi*surfnx
229
 
   diipb(2,ifac) = vecigy - psi*surfny
230
 
   diipb(3,ifac) = vecigz - psi*surfnz
231
 
 
232
 
enddo
233
 
 
234
 
!===============================================================================
235
 
! 3. FIN
236
 
!===============================================================================
237
 
 
238
 
return
239
 
end subroutine