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

« back to all changes in this revision

Viewing changes to src/comb/cs_fuel_physprop2.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 cs_fuel_physprop2 &
 
24
!================
 
25
 
 
26
 ( ncelet , ncel   ,                              &
 
27
   rtp    , propce )
 
28
 
 
29
!===============================================================================
 
30
! FONCTION :
 
31
! --------
 
32
 
 
33
! CALCUL DES PROPRIETES PHYSIQUES DE LA PHASE DISPERSEE
 
34
! VALEURS CELLULES
 
35
! ----------------
 
36
 
 
37
!   FRACTION MASSIQUE DE LIQUIDE
 
38
!     ET CLIPPING EVENTUELS
 
39
!   DIAMETRE
 
40
!   MASSE VOLUMIQUE
 
41
!     ET CLIPPING EVENTUELS
 
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
! rtp              ! tr ! <-- ! variables de calcul au centre des              !
 
50
! (ncelet,*)       !    !     !    cellules (instant courant)                  !
 
51
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
 
52
!__________________!____!_____!________________________________________________!
 
53
 
 
54
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
55
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
56
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
57
!            --- tableau de travail
 
58
!===============================================================================
 
59
 
 
60
!===============================================================================
 
61
! Module files
 
62
!===============================================================================
 
63
 
 
64
use paramx
 
65
use numvar
 
66
use optcal
 
67
use cstphy
 
68
use entsor
 
69
use cstnum
 
70
use parall
 
71
use ppppar
 
72
use ppthch
 
73
use coincl
 
74
use cpincl
 
75
use cs_fuel_incl
 
76
use ppincl
 
77
 
 
78
!===============================================================================
 
79
 
 
80
implicit none
 
81
 
 
82
! Arguments
 
83
 
 
84
integer          ncelet , ncel
 
85
 
 
86
double precision rtp(ncelet,*) , propce(ncelet,*)
 
87
 
 
88
! Local variables
 
89
 
 
90
integer          iel
 
91
integer          n1     , n2     , ipcdia , ipcro2 , icla
 
92
double precision xnp    ,  d1s3
 
93
double precision rhofol , diam2m , diam2x
 
94
 
 
95
!===============================================================================
 
96
 
 
97
!===============================================================================
 
98
! 1. INITIALISATIONS
 
99
!===============================================================================
 
100
 
 
101
d1s3 = 1.d0/3.d0
 
102
 
 
103
!===============================================================================
 
104
! 2. CALCUL POUR CHAQUE CLASSE
 
105
!    DE LA MASSE VOLUMIQUE DU FOL
 
106
!    DE LA FRACTION MASSIQUE DE FOL
 
107
!    DU DIAMETRE DU COKE
 
108
!===============================================================================
 
109
 
 
110
do icla = 1, nclafu
 
111
 
 
112
  n1 = 0
 
113
  n2 = 0
 
114
  diam2m =  1.d0
 
115
  diam2x =  0.d0
 
116
 
 
117
  ipcdia = ipproc(idiam2(icla))
 
118
  ipcro2 = ipproc(irom2 (icla))
 
119
 
 
120
  do iel = 1, ncel
 
121
 
 
122
!  Masse Volumique
 
123
    propce(iel,ipcro2) = rho0fl
 
124
!
 
125
! --- Calcul du diametre de la particule
 
126
!
 
127
    yfol   = rtp(iel,isca(iyfol(icla)))
 
128
    xnp    = rtp(iel,isca(ing  (icla)))
 
129
    if ( yfol .gt. epsifl .and. (xnp*yfol) .gt. 0.d0) then
 
130
 
 
131
      propce(iel,ipcdia) = ( (yfol / propce(iel,ipcro2) )           &
 
132
                            /(pi/6.d0 * xnp) ) ** d1s3
 
133
 
 
134
      if ( propce(iel,ipcdia) .gt. dinifl(icla) ) then
 
135
        n1 = n1+1
 
136
        diam2x = max(diam2x,propce(iel,ipcdia))
 
137
        propce(iel,ipcdia) = dinifl(icla)
 
138
      endif
 
139
 
 
140
      if ( propce(iel,ipcdia) .lt. diniin(icla) ) then
 
141
        n2 = n2+1
 
142
        diam2m = min(diam2m,propce(iel,ipcdia))
 
143
        propce(iel,ipcdia) = diniin(icla)
 
144
      endif
 
145
 
 
146
    else
 
147
      propce(iel,ipcdia) = dinifl(icla)
 
148
    endif
 
149
 
 
150
  enddo
 
151
 
 
152
  if (irangp.ge.0) then
 
153
 
 
154
    call parcpt (n1)
 
155
    !==========
 
156
    call parcpt (n2)
 
157
    !==========
 
158
 
 
159
    call parmax (diam2x)
 
160
    !==========
 
161
    call parmin (diam2m)
 
162
    !==========
 
163
  endif
 
164
 
 
165
  if ( n1 .gt. 0 ) then
 
166
    write(nfecra,1001) icla, n1, diam2x
 
167
  endif
 
168
  if ( n2 .gt. 0 ) then
 
169
    write(nfecra,1002)  icla, n2, diam2m
 
170
  endif
 
171
 
 
172
enddo
 
173
 
 
174
!----
 
175
! Formats
 
176
!----
 
177
 
 
178
 1001 format(/,1X,' CLIPPING EN MAX DU DIAMETRE CLASSE :',I2,           &
 
179
       /,10X,' Nombre de points : ',I8,                           &
 
180
       /,10X,' Valeur Max       : ',G15.7)
 
181
 1002 format(/,1X,' CLIPPING EN MIN DU DIAMETRE CLASSE :',I2,           &
 
182
       /,10X,' Nombre de points : ',I8,                           &
 
183
       /,10X,' Valeur Min       : ',G15.7)
 
184
 
 
185
 
 
186
!----
 
187
! End
 
188
!----
 
189
 
 
190
return
 
191
end subroutine