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

« back to all changes in this revision

Viewing changes to src/comb/cs_coal_prop.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 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_coal_prop &
 
24
!======================
 
25
 ( ipropp , ipppst )
 
26
 
 
27
!===============================================================================
 
28
!  FONCTION  :
 
29
!  ---------
 
30
 
 
31
! INIT DES POSITIONS DES VARIABLES D'ETAT SELON
 
32
!         COMBUSTION CHARBON PULVERISE
 
33
!   (DANS VECTEURS PROPCE, PROPFA, PROPFB)
 
34
 
 
35
!-------------------------------------------------------------------------------
 
36
! Arguments
 
37
!__________________.____._____.________________________________________________.
 
38
! name             !type!mode ! role                                           !
 
39
!__________________!____!_____!________________________________________________!
 
40
! ipropp           ! e  ! <-- ! numero de la derniere propriete                !
 
41
!                  !    !     !  (les proprietes sont dans propce,             !
 
42
!                  !    !     !   propfa ou prpfb)                             !
 
43
! ipppst           ! e  ! <-- ! pointeur indiquant le rang de la               !
 
44
!                  !    !     !  derniere grandeur definie aux                 !
 
45
!                  !    !     !  cellules (rtp,propce...) pour le              !
 
46
!                  !    !     !  post traitement                               !
 
47
!__________________!____!_____!________________________________________________!
 
48
 
 
49
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
50
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
51
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
52
!            --- tableau de travail
 
53
!===============================================================================
 
54
 
 
55
!===============================================================================
 
56
! Module files
 
57
!===============================================================================
 
58
 
 
59
use paramx
 
60
use dimens
 
61
use numvar
 
62
use optcal
 
63
use cstphy
 
64
use entsor
 
65
use cstnum
 
66
use ppppar
 
67
use ppthch
 
68
use ppcpfu
 
69
use coincl
 
70
use cpincl
 
71
use ppincl
 
72
use ihmpre
 
73
use cs_coal_incl
 
74
 
 
75
!===============================================================================
 
76
 
 
77
implicit none
 
78
 
 
79
! Arguments
 
80
 
 
81
integer       ipropp, ipppst
 
82
 
 
83
! Local variables
 
84
 
 
85
integer       iprop, ige , icla, iprop2
 
86
 
 
87
!===============================================================================
 
88
 
 
89
! ---> Definition des pointeurs relatifs aux variables d'etat
 
90
 
 
91
iprop = ipropp
 
92
 
 
93
!    Phase continue (melange gazeux)
 
94
iprop   = iprop + 1
 
95
itemp1  = iprop
 
96
iprop   = iprop + 1
 
97
irom1  = iprop
 
98
do ige = 1,ngazg
 
99
! ---- Cf. definition de NGAZE dans cs_coal_readata
 
100
  iprop     = iprop + 1
 
101
  iym1(ige) = iprop
 
102
enddo
 
103
iprop = iprop + 1
 
104
immel = iprop
 
105
!
 
106
if ( ieqnox .eq. 1 ) then
 
107
  iprop  = iprop + 1
 
108
  ighcn1 = iprop
 
109
  iprop  = iprop + 1
 
110
  ighcn2 = iprop
 
111
  iprop  = iprop + 1
 
112
  ignoth = iprop
 
113
endif
 
114
 
 
115
iprop2 = iprop
 
116
 
 
117
!   Phase dispersee (classes de particules)
 
118
do icla = 1, nclacp
 
119
  iprop        = iprop2 + icla
 
120
  itemp2(icla) = iprop
 
121
  iprop        = iprop2 + 1*nclacp + icla
 
122
  ix2(icla)    = iprop
 
123
  iprop        = iprop2 + 2*nclacp + icla
 
124
  irom2(icla)  = iprop
 
125
  iprop        = iprop2 + 3*nclacp + icla
 
126
  idiam2(icla) = iprop
 
127
  iprop        = iprop2 + 4*nclacp + icla
 
128
  igmdch(icla) = iprop
 
129
  iprop        = iprop2 + 5*nclacp + icla
 
130
  igmdv1(icla) = iprop
 
131
  iprop        = iprop2 + 6*nclacp + icla
 
132
  igmdv2(icla) = iprop
 
133
  iprop        = iprop2 + 7*nclacp + icla
 
134
  igmhet(icla) = iprop
 
135
  if ( ihtco2 .eq. 1 ) then
 
136
    iprop        = iprop2 + 8*nclacp + icla
 
137
    ighco2(icla) = iprop
 
138
    if ( ihth2o .eq. 1 ) then
 
139
      iprop        = iprop2 + 9*nclacp + icla
 
140
      ighh2o(icla) = iprop
 
141
      if ( ippmod(iccoal) .ge. 1 ) then
 
142
        iprop        = iprop2 + 10*nclacp + icla
 
143
        igmsec(icla) = iprop
 
144
      endif
 
145
    else
 
146
      if ( ippmod(iccoal) .ge. 1 ) then
 
147
        iprop        = iprop2 + 9*nclacp + icla
 
148
        igmsec(icla) = iprop
 
149
      endif
 
150
    endif
 
151
  else
 
152
    if ( ihth2o .eq. 1 ) then
 
153
      iprop        = iprop2 + 8*nclacp + icla
 
154
      ighh2o(icla) = iprop
 
155
      if ( ippmod(iccoal) .ge. 1 ) then
 
156
        iprop        = iprop2 + 9*nclacp + icla
 
157
        igmsec(icla) = iprop
 
158
      endif
 
159
    else
 
160
      if ( ippmod(iccoal) .ge. 1 ) then
 
161
        iprop        = iprop2 + 8*nclacp + icla
 
162
        igmsec(icla) = iprop
 
163
      endif
 
164
    endif
 
165
  endif
 
166
enddo
 
167
 
 
168
!
 
169
! Bilan : C , O , H
 
170
!
 
171
iprop     = iprop + 1
 
172
ibcarbone = iprop
 
173
iprop     = iprop + 1
 
174
iboxygen  = iprop
 
175
iprop     = iprop + 1
 
176
ibhydrogen= iprop
 
177
 
 
178
! ---- Nb de variables algebriques (ou d'etat)
 
179
!         propre a la physique particuliere NSALPP
 
180
!         total NSALTO
 
181
 
 
182
nsalpp = iprop - ipropp
 
183
nsalto = iprop
 
184
 
 
185
! ----  On renvoie IPROPP au cas ou d'autres proprietes devraient
 
186
!         etre numerotees ensuite
 
187
 
 
188
ipropp = iprop
 
189
 
 
190
! ---> Positionnement dans le tableau PROPCE
 
191
!      et reperage du rang pour le post-traitement
 
192
 
 
193
iprop         = nproce
 
194
 
 
195
!    Phase continue (melange gazeux)
 
196
iprop           = iprop + 1
 
197
ipproc(itemp1)  = iprop
 
198
ipppst          = ipppst + 1
 
199
ipppro(iprop)   = ipppst
 
200
 
 
201
iprop           = iprop + 1
 
202
ipproc(irom1)   = iprop
 
203
ipppst          = ipppst + 1
 
204
ipppro(iprop)   = ipppst
 
205
 
 
206
do ige = 1, (ngaze-2*ncharb)
 
207
! ---- Cf. definition de NGAZE dans cs_coal_readata
 
208
  iprop                 = iprop + 1
 
209
  ipproc(iym1(ige))     = iprop
 
210
  ipppst                = ipppst + 1
 
211
  ipppro(iprop)         = ipppst
 
212
enddo
 
213
 
 
214
iprop                 = iprop + 1
 
215
ipproc(immel)         = iprop
 
216
ipppst                = ipppst + 1
 
217
ipppro(iprop)         = ipppst
 
218
 
 
219
!
 
220
if ( ieqnox .eq. 1 ) then
 
221
  iprop                 = iprop + 1
 
222
  ipproc(ighcn1)        = iprop
 
223
  ipppst                = ipppst + 1
 
224
  ipppro(iprop)         = ipppst
 
225
!
 
226
  iprop                 = iprop + 1
 
227
  ipproc(ighcn2)        = iprop
 
228
  ipppst                = ipppst + 1
 
229
  ipppro(iprop)         = ipppst
 
230
!
 
231
  iprop                 = iprop + 1
 
232
  ipproc(ignoth)        = iprop
 
233
  ipppst                = ipppst + 1
 
234
  ipppro(iprop)         = ipppst
 
235
endif
 
236
 
 
237
iprop2 = iprop
 
238
 
 
239
!   Phase dispersee (classes de particules)
 
240
do icla = 1, nclacp
 
241
 
 
242
  iprop                 = iprop2 + icla
 
243
  ipproc(itemp2(icla))  = iprop
 
244
  ipppst                = ipppst + 1
 
245
  ipppro(iprop)         = ipppst
 
246
 
 
247
  iprop                 = iprop2 + 1*nclacp + icla
 
248
  ipproc(ix2(icla))     = iprop
 
249
  ipppst                = ipppst + 1
 
250
  ipppro(iprop)         = ipppst
 
251
 
 
252
  iprop                 = iprop2 + 2*nclacp + icla
 
253
  ipproc(irom2(icla))   = iprop
 
254
  ipppst                = ipppst + 1
 
255
  ipppro(iprop)         = ipppst
 
256
 
 
257
  iprop                 = iprop2 + 3*nclacp + icla
 
258
  ipproc(idiam2(icla))  = iprop
 
259
  ipppst                = ipppst + 1
 
260
  ipppro(iprop)         = ipppst
 
261
 
 
262
  iprop                 = iprop2 + 4*nclacp + icla
 
263
  ipproc(igmdch(icla))  = iprop
 
264
  ipppst                = ipppst + 1
 
265
  ipppro(iprop)         = ipppst
 
266
 
 
267
  iprop                 = iprop2 + 5*nclacp + icla
 
268
  ipproc(igmdv1(icla))  = iprop
 
269
  ipppst                = ipppst + 1
 
270
  ipppro(iprop)         = ipppst
 
271
 
 
272
  iprop                 = iprop2 + 6*nclacp + icla
 
273
  ipproc(igmdv2(icla))  = iprop
 
274
  ipppst                = ipppst + 1
 
275
  ipppro(iprop)         = ipppst
 
276
 
 
277
  iprop                 = iprop2 + 7*nclacp + icla
 
278
  ipproc(igmhet(icla))  = iprop
 
279
  ipppst                = ipppst + 1
 
280
  ipppro(iprop)         = ipppst
 
281
 
 
282
  if ( ihtco2 .eq. 1 ) then
 
283
    iprop                 = iprop2 + 8*nclacp + icla
 
284
    ipproc(ighco2(icla))  = iprop
 
285
    ipppst                = ipppst + 1
 
286
    ipppro(iprop)         = ipppst
 
287
 
 
288
    if ( ihth2o .eq. 1 ) then
 
289
      iprop                 = iprop2 + 9*nclacp + icla
 
290
      ipproc(ighh2o(icla))  = iprop
 
291
      ipppst                = ipppst + 1
 
292
      ipppro(iprop)         = ipppst
 
293
 
 
294
      if ( ippmod(iccoal) .eq. 1 ) then
 
295
        iprop                 = iprop2 + 10*nclacp + icla
 
296
        ipproc(igmsec(icla))  = iprop
 
297
        ipppst                = ipppst + 1
 
298
        ipppro(iprop)         = ipppst
 
299
      endif
 
300
 
 
301
    else
 
302
      if ( ippmod(iccoal) .eq. 1 ) then
 
303
        iprop                 = iprop2 + 9*nclacp + icla
 
304
        ipproc(igmsec(icla))  = iprop
 
305
        ipppst                = ipppst + 1
 
306
        ipppro(iprop)         = ipppst
 
307
      endif
 
308
    endif
 
309
 
 
310
  else
 
311
    if ( ihth2o .eq. 1 ) then
 
312
      iprop                 = iprop2 + 8*nclacp + icla
 
313
      ipproc(ighh2o(icla))  = iprop
 
314
      ipppst                = ipppst + 1
 
315
      ipppro(iprop)         = ipppst
 
316
 
 
317
      if ( ippmod(iccoal) .eq. 1 ) then
 
318
        iprop                 = iprop2 + 9*nclacp + icla
 
319
        ipproc(igmsec(icla))  = iprop
 
320
        ipppst                = ipppst + 1
 
321
        ipppro(iprop)         = ipppst
 
322
      endif
 
323
 
 
324
    else
 
325
      if ( ippmod(iccoal) .eq. 1 ) then
 
326
        iprop                 = iprop2 + 8*nclacp + icla
 
327
        ipproc(igmsec(icla))  = iprop
 
328
        ipppst                = ipppst + 1
 
329
        ipppro(iprop)         = ipppst
 
330
      endif
 
331
    endif
 
332
  endif
 
333
 
 
334
enddo
 
335
!
 
336
! Bilan C , O , H
 
337
!
 
338
iprop              = iprop  + 1
 
339
ipproc(ibcarbone)  = iprop
 
340
ipppst             = ipppst + 1
 
341
ipppro(iprop)      = ipppst
 
342
!
 
343
iprop              = iprop  + 1
 
344
ipproc(iboxygen)   = iprop
 
345
ipppst             = ipppst + 1
 
346
ipppro(iprop)      = ipppst
 
347
!
 
348
iprop              = iprop  + 1
 
349
ipproc(ibhydrogen) = iprop
 
350
ipppst             = ipppst + 1
 
351
ipppro(iprop)      = ipppst
 
352
!
 
353
nproce = iprop
 
354
 
 
355
 
 
356
! ---> Positionnement dans le tableau PROPFB
 
357
!      Au centre des faces de bord
 
358
 
 
359
iprop = nprofb
 
360
nprofb = iprop
 
361
 
 
362
! ---> Positionnement dans le tableau PROPFA
 
363
!      Au centre des faces internes (flux de masse)
 
364
 
 
365
iprop = nprofa
 
366
nprofa = iprop
 
367
 
 
368
 
 
369
!   - Interface Code_Saturne
 
370
!     ======================
 
371
!     Construction de l'indirection entre la numerotation du noyau et XML
 
372
if (iihmpr.eq.1) then
 
373
  call uicppr &
 
374
  !==========
 
375
 ( nclacp, nsalpp, nsalto, ippmod, iccoal, ipppro,    &
 
376
   ipproc, ihtco2, itemp1, irom1, iym1, immel,        &
 
377
   itemp2, ix2, irom2, idiam2, igmdch, igmdv1,        &
 
378
   igmdv2, igmhet, ighco2, igmsec)
 
379
endif
 
380
 
 
381
!--------
 
382
! Formats
 
383
!--------
 
384
 
 
385
!----
 
386
! End
 
387
!----
 
388
 
 
389
return
 
390
end subroutine