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

« back to all changes in this revision

Viewing changes to src/comb/cs_coal_htconvers2.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_coal_htconvers2 &
 
24
!============================
 
25
 ( mode , icla , enthal , xsolid , temper , t1)
 
26
!===============================================================================
 
27
!  FONCTION  :
 
28
!  --------
 
29
! CALCUL DE LA TEMPERATURE DES PARTICULES
 
30
!  EN FONCTION DE L'ENTHALPIE ET DES CONCENTRATIONS
 
31
!  SI IMODE = 1
 
32
! CALCUL DE L'ENTHALPIE DES PARTICULES
 
33
!  EN FONCTION DE LA TEMPERATURE ET DES CONCENTRATIONS
 
34
!  SI IMODE = -1
 
35
!-------------------------------------------------------------------------------
 
36
! Arguments
 
37
!__________________.____._____.________________________________________________.
 
38
! name             !type!mode ! role                                           !
 
39
!__________________!____!_____!________________________________________________!
 
40
! mode             ! e  ! <-- !  -1 : t -> h  ;   1 : h -> t                   !
 
41
! icla             ! e  ! <-- ! numero de la classe                            !
 
42
! enthal           ! r  ! <-- ! enthalpie massique j/kg                        !
 
43
! xsolid           ! tr ! <-- ! fraction massique des constituants             !
 
44
! temper           ! r  ! <-- ! temperature en kelvin                          !
 
45
!__________________!____!_____!________________________________________________!
 
46
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
47
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
48
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
49
!            --- tableau de travail
 
50
!===============================================================================
 
51
 
 
52
!===============================================================================
 
53
! Module files
 
54
!===============================================================================
 
55
 
 
56
use paramx
 
57
use pointe
 
58
use entsor
 
59
use cstnum
 
60
use cstphy
 
61
use ppppar
 
62
use ppthch
 
63
use coincl
 
64
use cpincl
 
65
use ppincl
 
66
 
 
67
!===============================================================================
 
68
 
 
69
implicit none
 
70
 
 
71
! Arguments
 
72
 
 
73
integer          mode , icla , icha
 
74
 
 
75
double precision xsolid(nsolim)
 
76
double precision temper , enthal , t1
 
77
 
 
78
! Local variables
 
79
 
 
80
integer          it , isol , ihflt2
 
81
 
 
82
double precision eh1 , eh0 , x2
 
83
 
 
84
!===============================================================================
 
85
! Mode de conversion
 
86
ihflt2 = 1
 
87
 
 
88
if ( ihflt2.eq.0 ) then
 
89
 
 
90
!===============================================================================
 
91
! 2. H2 FONCTION LINEAIRE T2
 
92
!===============================================================================
 
93
 
 
94
  icha = ichcor(icla)
 
95
 
 
96
  if ( mode.eq.-1 ) then
 
97
 
 
98
! --> Loi temperature -> enthalpie (MODE = -1)
 
99
 
 
100
    enthal = h02ch(icha) + cp2ch(icha)*(temper-trefth)
 
101
 
 
102
  elseif ( mode.eq.1 ) then
 
103
 
 
104
! --> Loi enthalpie -> temperature (MODE = 1)
 
105
 
 
106
    temper =  (enthal-h02ch(icha))/cp2ch(icha) + trefth
 
107
 
 
108
  else
 
109
 
 
110
    write(nfecra,1000) mode
 
111
    call csexit (1)
 
112
    !==========
 
113
 
 
114
  endif
 
115
 
 
116
 
 
117
elseif( ihflt2.ne.0 ) then
 
118
 
 
119
!===============================================================================
 
120
! 3. H2 TABULE
 
121
!===============================================================================
 
122
 
 
123
  if ( mode.eq.-1 ) then
 
124
 
 
125
! --> Loi temperature -> enthalpie (MODE = -1)
 
126
 
 
127
    it = npoc
 
128
    if ( temper.ge.thc(it) ) then
 
129
      enthal = zero
 
130
      do isol = 1, nsolid
 
131
        enthal = enthal + xsolid(isol)*ehsoli(isol,it)
 
132
      enddo
 
133
      go to 11
 
134
    endif
 
135
 
 
136
    it = 1
 
137
    if ( temper.le.thc(it) ) then
 
138
      enthal = zero
 
139
      do isol = 1, nsolid
 
140
        enthal = enthal + xsolid(isol)*ehsoli(isol,it)
 
141
      enddo
 
142
      go to 11
 
143
    endif
 
144
    it = 1
 
145
 10       continue
 
146
 
 
147
    it = it + 1
 
148
    if ( temper.le.thc(it) ) then
 
149
      eh0 = zero
 
150
      eh1 = zero
 
151
      do isol = 1, nsolid
 
152
        eh0 = eh0 + xsolid(isol)*ehsoli(isol,it-1)
 
153
        eh1 = eh1 + xsolid(isol)*ehsoli(isol,it  )
 
154
      enddo
 
155
      enthal = eh0                                                &
 
156
             + (eh1-eh0)*(temper-thc(it-1))                       &
 
157
                        /(thc(it)-thc(it-1))
 
158
      goto 11
 
159
    endif
 
160
    goto 10
 
161
 11       continue
 
162
 
 
163
  elseif ( mode.eq.1 ) then
 
164
 
 
165
! --> Loi enthalpie -> temperature (MODE = 1)
 
166
 
 
167
    x2 = 0.d0
 
168
    do isol = 1, nsolid
 
169
      x2 = x2 + xsolid(isol)
 
170
    enddo
 
171
 
 
172
    if ( x2 .gt. epsicp ) then
 
173
      it  = npoc-1
 
174
      eh1 = zero
 
175
      do isol = 1, nsolid
 
176
        eh1 = eh1 + xsolid(isol)*ehsoli(isol,it+1)
 
177
      enddo
 
178
      if ( enthal.ge.eh1 ) temper = thc(it+1)
 
179
 
 
180
      it  = 1
 
181
      eh0 = zero
 
182
      do isol = 1, nsolid
 
183
        eh0 = eh0 + xsolid(isol)*ehsoli(isol,it  )
 
184
      enddo
 
185
      if ( enthal.le.eh0 ) temper = thc(it)
 
186
 
 
187
      do it = 1, npoc-1
 
188
        eh0 = zero
 
189
        eh1 = zero
 
190
        do isol = 1, nsolid
 
191
          eh0 = eh0 + xsolid(isol)*ehsoli(isol,it  )
 
192
          eh1 = eh1 + xsolid(isol)*ehsoli(isol,it+1)
 
193
        enddo
 
194
        if ( enthal.ge.eh0 .and. enthal.le.eh1 )                  &
 
195
          temper = thc(it)                                        &
 
196
            + (enthal-eh0)*(thc(it+1)-thc(it))/(eh1-eh0)
 
197
 
 
198
      enddo
 
199
 
 
200
    else
 
201
      temper = t1
 
202
    endif
 
203
 
 
204
  else
 
205
 
 
206
    write(nfecra,1000) mode
 
207
    call csexit (1)
 
208
    !==========
 
209
 
 
210
  endif
 
211
 
 
212
endif
 
213
 
 
214
!--------
 
215
! Formats
 
216
!--------
 
217
 
 
218
 1000 format(                                                     &
 
219
'@                                                            ',/,&
 
220
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
221
'@                                                            ',/,&
 
222
'@ @@ ATTENTION : ERREUR DANS CS_COAL_HT_CONVERS2             ',/,&
 
223
'@    =========                                               ',/,&
 
224
'@    VALEUR INCORRECTE DE L''ARGUMENT MODE                   ',/,&
 
225
'@    CE DOIT ETRE UN ENTIER EGAL A 1 OU -1                   ',/,&
 
226
'@    IL VAUT ICI ',I10                                        ,/,&
 
227
'@                                                            ',/,&
 
228
'@  Le calcul ne peut etre execute.                           ',/,&
 
229
'@                                                            ',/,&
 
230
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
231
'@                                                            ',/)
 
232
 
 
233
 
 
234
!----
 
235
! End
 
236
!----
 
237
 
 
238
return
 
239
end subroutine