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

« back to all changes in this revision

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