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

« back to all changes in this revision

Viewing changes to src/turb/clpv2f.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 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 clpv2f &
 
24
!================
 
25
 
 
26
 ( ncelet , ncel   , nvar   ,                                     &
 
27
   iwaphi ,                                                       &
 
28
   propce , rtp    )
 
29
 
 
30
!===============================================================================
 
31
! FONCTION :
 
32
! ----------
 
33
 
 
34
! CLIPPING DE PHI EN V2F (PAS DE CLIPPING SUR F_BARRE)
 
35
 
 
36
!-------------------------------------------------------------------------------
 
37
! Arguments
 
38
!ARGU                             ARGUMENTS
 
39
!__________________.____._____.________________________________________________.
 
40
! name             !type!mode ! role                                           !
 
41
!__________________!____!_____!________________________________________________!
 
42
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
 
43
! ncel             ! e  ! <-- ! nombre de cellules                             !
 
44
! nvar             ! e  ! <-- ! nombre de variables                            !
 
45
! iwaphi           ! e  ! <-- ! niveau d'impression                            !
 
46
! propce           ! tr ! <-- ! tableaux des variables au pdt courant          !
 
47
!(ncelet,*         !    !     !                                                !
 
48
! rtp              ! tr ! <-- ! tableaux des variables au pdt courant          !
 
49
! (ncelet,nvar)    !    !     !                                                !
 
50
!__________________!____!_____!________________________________________________!
 
51
 
 
52
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
53
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
54
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
55
!            --- tableau de travail
 
56
!===============================================================================
 
57
 
 
58
!===============================================================================
 
59
! Module files
 
60
!===============================================================================
 
61
 
 
62
use paramx
 
63
use entsor
 
64
use numvar
 
65
use cstnum
 
66
use parall
 
67
use optcal
 
68
 
 
69
!===============================================================================
 
70
 
 
71
implicit none
 
72
 
 
73
! Arguments
 
74
 
 
75
integer          nvar, ncelet, ncel
 
76
integer          iwaphi
 
77
double precision propce(ncelet,*)
 
78
double precision rtp(ncelet,nvar)
 
79
 
 
80
! Local variables
 
81
 
 
82
integer          iel, ipp
 
83
integer          nclpmx, nclpmn
 
84
double precision xphi, xal, vmin, vmax, var
 
85
 
 
86
!===============================================================================
 
87
 
 
88
!===============================================================================
 
89
!  1. Pour le phi-fbar et BL-v2/k model, reperage des valeurs de phi
 
90
!     superieures a 2 et clipping de phi en valeur absolue
 
91
!     pour les valeurs negatives
 
92
!===============================================================================
 
93
 
 
94
!===============================================================================
 
95
!     1.a Stockage Min et Max pour listing
 
96
!===============================================================================
 
97
 
 
98
ipp = ipprtp(iphi)
 
99
 
 
100
vmin =  grand
 
101
vmax = -grand
 
102
do iel = 1, ncel
 
103
  var = rtp(iel,iphi)
 
104
  vmin = min(vmin,var)
 
105
  vmax = max(vmax,var)
 
106
enddo
 
107
if (irangp.ge.0) then
 
108
  call parmin(vmin)
 
109
  !==========
 
110
  call parmax(vmax)
 
111
  !==========
 
112
endif
 
113
varmna(ipp) = vmin
 
114
varmxa(ipp) = vmax
 
115
 
 
116
!==============================================================================
 
117
!     1.b Reperage des valeurs superieures a 2, pour affichage seulement
 
118
!==============================================================================
 
119
 
 
120
if (iwaphi.ge.2) then
 
121
  nclpmx = 0
 
122
  do iel = 1, ncel
 
123
    if (rtp(iel,iphi).gt.2.d0) nclpmx = nclpmx+1
 
124
  enddo
 
125
  if(irangp.ge.0) call parcpt(nclpmx)
 
126
                  !==========
 
127
  if (nclpmx.gt.0) write(nfecra,1000) nclpmx
 
128
endif
 
129
 
 
130
!==============================================================================
 
131
!     1.c Clipping en valeur absolue pour les valeurs negatives
 
132
!==============================================================================
 
133
 
 
134
nclpmn = 0
 
135
do iel = 1, ncel
 
136
  xphi = rtp(iel,iphi)
 
137
  if (xphi.lt.0.d0) then
 
138
    rtp(iel,iphi) = -xphi
 
139
    nclpmn = nclpmn + 1
 
140
  endif
 
141
enddo
 
142
if(irangp.ge.0) call parcpt(nclpmn)
 
143
                !==========
 
144
iclpmn(ipp) = nclpmn
 
145
 
 
146
!===============================================================================
 
147
!  2. Pour le BL-v2/k model, clipping de alpha a 0 pour les valeurs negatives
 
148
!     et a 1 pour les valeurs superieurs a 1
 
149
!===============================================================================
 
150
 
 
151
if(iturb.eq.51) then
 
152
 
 
153
!===============================================================================
 
154
!     2.a Stockage Min et Max pour listing
 
155
!===============================================================================
 
156
 
 
157
  ipp = ipprtp(ial)
 
158
 
 
159
  vmin =  grand
 
160
  vmax = -grand
 
161
  do iel = 1, ncel
 
162
    var = rtp(iel,ial)
 
163
    vmin = min(vmin,var)
 
164
    vmax = max(vmax,var)
 
165
  enddo
 
166
  if (irangp.ge.0) then
 
167
    call parmin(vmin)
 
168
    !==========
 
169
    call parmax(vmax)
 
170
    !==========
 
171
  endif
 
172
  varmna(ipp) = vmin
 
173
  varmxa(ipp) = vmax
 
174
 
 
175
!==============================================================================
 
176
!     2.b Clipping a 0 pour les valeurs negatives et a 1 pour les valeurs
 
177
!         superieures a 1
 
178
!==============================================================================
 
179
 
 
180
  nclpmn = 0
 
181
  nclpmx = 0
 
182
  do iel = 1, ncel
 
183
    xal = rtp(iel,ial)
 
184
    if (xal.lt.0.d0) then
 
185
      rtp(iel,ial) = 0.d0
 
186
      nclpmn = nclpmn + 1
 
187
    endif
 
188
    if (xal.gt.1.d0) then
 
189
      rtp(iel,ial) = 1.d0
 
190
      nclpmx = nclpmx + 1
 
191
    endif
 
192
  enddo
 
193
  if(irangp.ge.0) then
 
194
    call parcpt(nclpmn)
 
195
    !==========
 
196
    call parcpt(nclpmx)
 
197
    !==========
 
198
  endif
 
199
  iclpmn(ipp) = nclpmn
 
200
  iclpmx(ipp) = nclpmx
 
201
 
 
202
endif
 
203
 
 
204
!===============================================================================
 
205
! ---> Formats
 
206
!===============================================================================
 
207
 
 
208
#if defined(_CS_LANG_FR)
 
209
 
 
210
 1000 format('ATTENTION VARIABLE PHI'                             &
 
211
     'VALEUR MAXIMALE PHYSIQUE DE 2 DEPASSEE SUR ',I10,           &
 
212
     ' CELLULES')
 
213
 
 
214
#else
 
215
 
 
216
 1000 format('WARNING VARIABLE PHI'                               &
 
217
     'MAXIMUM PHYSICAL VALUE OF 2 EXCEEDED FOR ',I10,             &
 
218
     ' CELLS')
 
219
 
 
220
#endif
 
221
 
 
222
return
 
223
 
 
224
end subroutine