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

« back to all changes in this revision

Viewing changes to src/base/clvolc.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 clvolc &
29
 
!================
30
 
 
31
 
 ( ncelet , ncel   ,                                              &
32
 
   volmin , volmax , voltot , volume )
33
 
 
34
 
!===============================================================================
35
 
 
36
 
!  FONCTION  :
37
 
!  --------
38
 
 
39
 
!     CALCUL DU VOLUME GEOMETRIQUE DES ELEMENTS
40
 
!     FORMULE DE GREEN : 3*VOLUME = SOMME DIV(R) AVEC R = t(X,Y,Z)
41
 
 
42
 
!-------------------------------------------------------------------------------
43
 
! Arguments
44
 
!__________________.____._____.________________________________________________.
45
 
! name             !type!mode ! role                                           !
46
 
!__________________!____!_____!________________________________________________!
47
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
48
 
! ncel             ! i  ! <-- ! number of cells                                !
49
 
! volmin           ! r  ! --> ! volume de controle minimal                     !
50
 
! volmax           ! r  ! --> ! volume de controle maximal                     !
51
 
! voltot           ! r  ! --> ! volume total du domaine                        !
52
 
! volume           ! tr ! --> ! volume d'un des ncelet elements                !
53
 
! (ncelet)         !    !     !                                                !
54
 
!__________________.____._____.________________________________________________.
55
 
 
56
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
57
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
58
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
59
 
!            --- tableau de travail
60
 
!===============================================================================
61
 
 
62
 
implicit none
63
 
 
64
 
!===============================================================================
65
 
! Common blocks
66
 
!===============================================================================
67
 
 
68
 
include "paramx.h"
69
 
include "optcal.h"
70
 
include "entsor.h"
71
 
include "period.h"
72
 
include "parall.h"
73
 
 
74
 
!===============================================================================
75
 
 
76
 
! Arguments
77
 
 
78
 
integer ncelet, ncel
79
 
double precision volmin, volmax, voltot
80
 
double precision volume(ncelet)
81
 
 
82
 
integer iel, idimte, itenso
83
 
 
84
 
integer          ipass
85
 
data             ipass /0/
86
 
save             ipass
87
 
 
88
 
!===============================================================================
89
 
! 1. INITIALISATION EFFECTUEE DANS cs_maillage_grd.c
90
 
!===============================================================================
91
 
 
92
 
ipass = ipass + 1
93
 
 
94
 
!===============================================================================
95
 
! 2. ON PREND LES MIN ET MAX
96
 
!===============================================================================
97
 
 
98
 
volmin =  1.d+12
99
 
volmax = -1.d+12
100
 
voltot = 0.d0
101
 
 
102
 
do iel  = 1, ncel
103
 
 
104
 
   volmin = min(volmin, volume(iel))
105
 
   volmax = max(volmax, volume(iel))
106
 
   voltot = voltot + volume(iel)
107
 
 
108
 
enddo
109
 
 
110
 
!       On communique le volume au halo pour les filtrages des modeles
111
 
!       dynamiques de L.E.S.
112
 
!       Dans le cas d'un voisinage etendu traite separement, l'appel a
113
 
!       PARCVE est fait directement dans la routine CFLITR (ce qui d'ailleurs
114
 
!       pourrait etre optimise)
115
 
if (irangp.ge.0) then
116
 
  call parcom(volume)
117
 
  !==========
118
 
  call parmin (volmin)
119
 
  !==========
120
 
  call parmax (volmax)
121
 
  !==========
122
 
  call parsom (voltot)
123
 
  !==========
124
 
endif
125
 
if(iperio.eq.1) then
126
 
 
127
 
  idimte = 0
128
 
  itenso = 0
129
 
 
130
 
  call percom                                                     &
131
 
  !==========
132
 
       ( idimte , itenso ,                                        &
133
 
         volume , volume , volume ,                               &
134
 
         volume , volume , volume ,                               &
135
 
         volume , volume , volume )
136
 
 
137
 
endif
138
 
 
139
 
!     En ALE, on passe plusieurs fois ici.
140
 
!     Au premier passage (avant calculs) on ecrit, on teste et on s'arrete
141
 
!       si pb.
142
 
!     Aux passages suivants, on n'ecrit pas, on teste et on finit le pas
143
 
!       de temps si pb.
144
 
if (ipass.eq.1) then
145
 
  write(nfecra,1000) volmin, volmax, voltot
146
 
  if (volmin.le.0.d0) then
147
 
    write(nfecra,1002)
148
 
    call csexit (1)
149
 
  endif
150
 
else
151
 
  if (volmin.le.0.d0) then
152
 
    write(nfecra,1001) volmin, volmax, voltot
153
 
    write(nfecra,1002)
154
 
    ntmabs = ntcabs
155
 
  endif
156
 
endif
157
 
!===============================================================================
158
 
! 5. FIN
159
 
!===============================================================================
160
 
 
161
 
#if defined(_CS_LANG_FR)
162
 
 
163
 
 1000 format(                                                           &
164
 
' --- Information sur les volumes                             ',/,&
165
 
'       Volume de controle minimal = ',4X,E18.9                ,/,&
166
 
'       Volume de controle maximal = ',4X,E18.9                ,/,&
167
 
'       Volume total du domaine    = ',4X,E18.9                 )
168
 
 1001 format(/,' CLVOLC : VOLUME DE CONTROLE MINIMAL     = ',E18.9,/,   &
169
 
         '          VOLUME DE CONTROLE MAXIMAL     = ',E18.9,/,   &
170
 
         '          VOLUME TOTAL DU DOMAINE        = ',E18.9,/,/)
171
 
 1002 format(/,' CLVOLC : ARRET SUITE A LA DETECTION D''UN',/,    &
172
 
         '          VOLUME NEGATIF',/)
173
 
 
174
 
#else
175
 
 
176
 
 1000 format(                                                           &
177
 
' --- Information on the volumes                              ',/,&
178
 
'       Minimum control volume      = ',4X,E18.9               ,/,&
179
 
'       Maximum control volume      = ',4X,E18.9               ,/,&
180
 
'       Total volume for the domain = ',4X,E18.9                 )
181
 
 1001 format(/,' CLVOLC : MINIMUM CONTROL VOLUME         = ',E18.9,/,   &
182
 
         '          MAXIMUM CONTROL VOLUME         = ',E18.9,/,   &
183
 
         '          TOTAL VOLUME FOR THE DOMAIN    = ',E18.9,/,/)
184
 
 1002 format(/,' CLVOLC : ABORT DUE TO THE DETECTION OF A ',/,    &
185
 
         '          NEGATIVE VOLUME',/)
186
 
 
187
 
#endif
188
 
 
189
 
return
190
 
end subroutine