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

« back to all changes in this revision

Viewing changes to src/base/proxav.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-01 17:43:32 UTC
  • mto: (6.1.7 sid)
  • mto: This revision was merged to the branch mainline in revision 11.
  • Revision ID: package-import@ubuntu.com-20111101174332-tl4vk45no0x3emc3
Tags: upstream-2.1.0
ImportĀ upstreamĀ versionĀ 2.1.0

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 proxav &
29
 
!================
30
 
 
31
 
 ( ncelet , ncel   , nfac   , isym   , iinvpe ,                   &
32
 
   ifacel , xa     , vx     , vy     )
33
 
 
34
 
!===============================================================================
35
 
! FONCTION :
36
 
! ----------
37
 
 
38
 
! PRODUIT MATRICE VECTEUR Y = (XA).X
39
 
 
40
 
!-------------------------------------------------------------------------------
41
 
!ARGU                             ARGUMENTS
42
 
!__________________.____._____.________________________________________________.
43
 
! name             !type!mode ! role                                           !
44
 
!__________________!____!_____!________________________________________________!
45
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
46
 
! ncel             ! i  ! <-- ! number of cells                                !
47
 
! nfac             ! i  ! <-- ! number of interior faces                       !
48
 
! isym             ! e  ! <-- ! indicateur = 1 matrice symetrique              !
49
 
!                  !    !     !            = 2 matrice non symetrique          !
50
 
! iinvpe           ! e  ! <-- ! indicateur pour annuler les increment          !
51
 
!                  !    !     ! en periodicite de rotation (=2) ou             !
52
 
!                  !    !     ! pour les echanger normalement de               !
53
 
!                  !    !     ! maniere scalaire (=1)                          !
54
 
! ifacel(2,nfac    ! te ! <-- ! no des elts voisins d'une face intern          !
55
 
! xa(nfac,isym)    ! tr ! <-- ! extra diagonale de la matrice                  !
56
 
! vx(ncelet        ! tr ! <-- ! vecteur a multiplier                           !
57
 
! vy(ncelet        ! tr ! --> ! vecteur resultat                               !
58
 
!__________________!____!_____!________________________________________________!
59
 
 
60
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
61
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
62
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
63
 
!            --- tableau de travail
64
 
!===============================================================================
65
 
 
66
 
implicit none
67
 
 
68
 
!===============================================================================
69
 
! Common blocks
70
 
!===============================================================================
71
 
 
72
 
include "paramx.h"
73
 
include "vector.h"
74
 
include "period.h"
75
 
include "parall.h"
76
 
 
77
 
!===============================================================================
78
 
 
79
 
 
80
 
! Arguments
81
 
 
82
 
integer          ncelet , ncel   , nfac   , isym , iinvpe
83
 
integer          ifacel(2,nfac)
84
 
double precision xa(nfac,isym),vx(ncelet),vy(ncelet)
85
 
 
86
 
! VARAIBLES LOCALES
87
 
 
88
 
integer ifac,ii,jj,iel,idimte,itenso
89
 
 
90
 
!===============================================================================
91
 
 
92
 
!     1 - PRODUIT MATRICE/VECTEUR PAR LA DIAGONALE
93
 
!     --------------------------------------------
94
 
 
95
 
do iel = 1, ncelet
96
 
  vy(iel) = 0.d0
97
 
enddo
98
 
 
99
 
 
100
 
!     2 - PRODUIT MATRICE/VECTEUR TERMES X-TRADIAGONAUX
101
 
!     -------------------------------------------------
102
 
 
103
 
! ---> TRAITEMENT DU PARALLELISME
104
 
 
105
 
if(irangp.ge.0) call parcom (vx)
106
 
                !==========
107
 
 
108
 
! --> TRAITEMENT DE LA PERIODICITE
109
 
if(iperio.eq.1) then
110
 
  if(iinvpe.eq.1) then
111
 
    idimte = 0
112
 
    itenso = 0
113
 
    call percom                                                   &
114
 
    !==========
115
 
  ( idimte , itenso ,                                             &
116
 
    vx     , vx     , vx    ,                                     &
117
 
    vx     , vx     , vx    ,                                     &
118
 
    vx     , vx     , vx    )
119
 
   elseif(iinvpe.eq.2) then
120
 
      idimte = 0
121
 
      itenso = 11
122
 
      call percom                                                 &
123
 
      !==========
124
 
  ( idimte , itenso ,                                             &
125
 
    vx     , vx     , vx    ,                                     &
126
 
    vx     , vx     , vx    ,                                     &
127
 
    vx     , vx     , vx    )
128
 
 
129
 
!        Utile a Codits (produit avec une variable non en increment)
130
 
    elseif(iinvpe.eq.3) then
131
 
      idimte = 0
132
 
      itenso = 1
133
 
      call percom                                                 &
134
 
      !==========
135
 
  ( idimte , itenso ,                                             &
136
 
    vx     , vx     , vx    ,                                     &
137
 
    vx     , vx     , vx    ,                                     &
138
 
    vx     , vx     , vx    )
139
 
    endif
140
 
endif
141
 
 
142
 
 
143
 
if( isym.eq.1 ) then
144
 
 
145
 
  if (ivecti.eq.1) then
146
 
 
147
 
!CDIR NODEP
148
 
    do ifac = 1,nfac
149
 
      ii = ifacel(1,ifac)
150
 
      jj = ifacel(2,ifac)
151
 
      vy(ii) = vy(ii) +xa(ifac,1)*vx(jj)
152
 
      vy(jj) = vy(jj) +xa(ifac,1)*vx(ii)
153
 
    enddo
154
 
 
155
 
  else
156
 
 
157
 
! VECTORISATION NON FORCEE
158
 
    do ifac = 1,nfac
159
 
      ii = ifacel(1,ifac)
160
 
      jj = ifacel(2,ifac)
161
 
      vy(ii) = vy(ii) +xa(ifac,1)*vx(jj)
162
 
      vy(jj) = vy(jj) +xa(ifac,1)*vx(ii)
163
 
    enddo
164
 
 
165
 
  endif
166
 
 
167
 
else
168
 
 
169
 
  if (ivecti.eq.1) then
170
 
 
171
 
!CDIR NODEP
172
 
    do ifac = 1,nfac
173
 
      ii = ifacel(1,ifac)
174
 
      jj = ifacel(2,ifac)
175
 
      vy(ii) = vy(ii) +xa(ifac,1)*vx(jj)
176
 
      vy(jj) = vy(jj) +xa(ifac,2)*vx(ii)
177
 
    enddo
178
 
 
179
 
  else
180
 
 
181
 
! VECTORISATION NON FORCEE
182
 
    do ifac = 1,nfac
183
 
      ii = ifacel(1,ifac)
184
 
      jj = ifacel(2,ifac)
185
 
      vy(ii) = vy(ii) +xa(ifac,1)*vx(jj)
186
 
      vy(jj) = vy(jj) +xa(ifac,2)*vx(ii)
187
 
    enddo
188
 
 
189
 
  endif
190
 
 
191
 
endif
192
 
 
193
 
!--------
194
 
! FORMATS
195
 
!--------
196
 
 
197
 
 
198
 
!----
199
 
! FIN
200
 
!----
201
 
 
202
 
return
203
 
 
204
 
end subroutine