1!-------------------------------------------------------------------------------
2
3! This file is part of Code_Saturne, a general-purpose CFD tool.
4!
5! Copyright (C) 1998-2021 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!> \file cs_fuel_incl.f90
24!> Module for heavy fuel oil combustion
25
26module cs_fuel_incl
27
28  !=============================================================================
29
30  use ppppar
31  use ppthch
32
33  implicit none
34
35  !      EPSIFL : Precision pour les tests
36
37  double precision epsifl
38  parameter ( epsifl = 1.d-8 )
39
40  !--> DONNEES RELATIVES AU FUEL
41
42  !      - Proprietes du fuel
43  !        CFOL      --> fractions massiques elementaires en C, H, O, S, In (%)
44  !        HFOL          du fuel oil liquid
45  !        OFOL
46  !        SFOL
47  !        XInFOL
48  !        PCIFOL    --> PCI (J/kg) fuel oil liquid
49  !        RHO0FL   --> Masse volumique initiale (kg/m3)
50
51  !      - Proprietes du coke
52  !        CKF      --> Fractions massiques elementaires en C, H, O, S, In (%)
53  !        HKF          du coke
54  !        OKF
55  !        SKF
56  !        XInKF
57  !        GAMMA    --> Composition du coke
58  !        DELTA        sous la forme CH(GAMMA)O(DELTA)
59  !                         GAMMA = HCK/CCK
60  !                         DELTA = OCK/CCK
61  !        PCIKF     --> PCI (J/kg) coke
62  !        RHOKF     --> Masse volumique coke
63  !        FKC       --> Fraction massique initiale de coke dans le fuel
64  !        H02FOL    --> H0 du fuel oil liquid
65  !        CPFOL     --> CP du fuel oil liquid
66  !        HRFVAP    --> H formation vapeur a Tebu
67  !        Fractions massiques dans les vapeurs
68  !        HSFOV     --> H2S
69  !        COFOV     --> CO
70  !        CHFOV     --> CHn
71  !        nHCFOV    --> n dans la formule CHn
72  !                      (un reel, car formule molaire moyenne)
73
74  !        DFOL      --> densite du fuel liquide
75
76  double precision, save :: cfol , hfol , ofol , sfol, xinfol,               &
77                            pcifol , rho0fl , rhokf,                         &
78                            h02fol , cp2fol , hrfvap, dfol,                  &
79                            ckf , hkf , okf , skf, xinkf, pcikf, fkc,        &
80                            hsfov, cofov, chfov, nhcfov
81
82  !      - Parametres pour l'evaporation
83  !      TEVAP1      --> temperature de debut d'evaporation
84  !      TEVAP2      --> temperature de fin d'evaporation
85
86  !        - Parametres cinetiques pour la combustion heterogene du coke
87  !          (Modele a sphere retrecissante)
88  !        AHETFL   --> Constante pre-exponentielle (kg/m2/s/atm)
89  !        EHETFL   --> Energie d'activation (kcal/mol)
90  !        IOFHET   --> Ordre de la reaction 0.5 si = 0 1 si = 1
91
92  integer, save :: iofhet
93  double precision, save :: yfol , afol  , efol  ,                           &
94                            ahetfl , ehetfl, tevap1, tevap2
95
96  !      - Enthalpie du fuel et coke
97  !     IFOL         --> Pointeur dans le tableau EHSOLI pour
98  !                         le fuel oil liquid
99  !     IKF          --> Pointeur dans le tableau EHSOLI pour
100  !                         le Coke
101  !     EHSOLI(S,IT) --> Enthalpie massique (J/kg) du constituant solide
102  !                         no S a la temperature T(IT)
103
104  integer, save :: ifol, ikf
105
106  ! ---- PAR CLASSES (grandeurs deduites)
107
108  !        NCLAFU     --> Nb de classes
109
110  integer(c_int), pointer, save :: nclafu
111
112  !      - Proprietes : on garde le meme max que pour le charbon qui
113  !        est definis dans ppppar.h
114  !        DINIFL(CL)  --> Diametre initial (mm)
115  !        DINIKF(CL)  --> Diametre coke (mm)
116  !        DINIIN(CL)  --> Diametre min (mm)
117
118  double precision, save :: dinifl(nclcpm),dinikf(nclcpm),diniin(nclcpm)
119
120  !--> DONNEES RELATIVES A LA COMBUSTION DES ESPECES GAZEUSES
121
122  !        IIFOV        --> Pointeur FOV   pour EHGAZE et WMOLE
123  !        IICO         --> Pointeur CO    pour EHGAZE et WMOLE
124  !        IIO2         --> Pointeur O2    pour EHGAZE et WMOLE
125  !        IICO2        --> Pointeur CO2   pour EHGAZE et WMOLE
126  !        IIH2O        --> Pointeur H2O   pour EHGAZE et WMOLE
127  !        IIN2         --> Pointeur N2    pour EHGAZE et WMOLE
128  !        IIH2S        --> Pointeur H2S   pour EHGAZE et WMOLE
129  !        IISO2        --> Pointeur SO2   pour EHGAZE et WMOLE
130
131  !        XSI         --> XSI = 3,76 pour de l'air
132  !        FVAPMX     --> Maximum pour le traceur F3
133  !        FOV         --> Composition de l'hydrocarbure relatif
134  !                        aux matieres volatiles
135  !        A,     --> Coefficients stoechiometriques molaires pour
136  !        B          la reaction d'evaporation
137
138  !        Concentrations dans les especes globales
139  !        AFOVF1         nb de moles de vapeur associees a un kg de traceur 1
140  !        ACOF1                          CO
141  !        AH2SF1                         H2S
142  !        AH2SF3                         H2S
143  !        AH2OF3                         H2O
144
145  integer, save :: ifov , ifo0
146  double precision, save :: fvapmx, fov, a, b
147
148  !--> DONNEES COMPLEMENTAIRES RELATIVES AU CALCUL DE RHO
149  !    SUR LES FACETTES DE BORD
150
151  !       IENTFL(IENT) --> Indicateur CFOL  par type de facette d'entree
152
153  integer, save :: ientfl(nozppm)
154
155  !--> GRANDEURS FOURNIES PAR L'UTILISATEUR EN CONDITIONS AUX LIMITES
156  !      PERMETTANT DE CALCULER AUTOMATIQUEMENT LA VITESSE, LA TURBULENCE,
157  !      L'ENTHALPIE D'ENTREE.
158
159  !    POUR LES ENTREES UNIQUEMENT , IENT ETANT LE NUMERO DE ZONE FRONTIERE
160
161  !       QIMPFL(IENT)      --> Debit      Fuel Oil Liquid     en kg/s
162  !       TIMPFL(IENT)      --> Temperature  FOL               en K
163
164  double precision, save :: qimpfl(nozppm), timpfl(nozppm)
165  double precision, save :: distfu(nozppm,nclcpm)
166  double precision, save :: hlfm
167
168  !--> POINTEURS DANS LE TABLEAU TBMCR
169
170  double precision, save :: afovf1,acof1,ah2sf1,ah2sf3
171
172  !=============================================================================
173
174  interface
175
176    !---------------------------------------------------------------------------
177
178    !> \cond DOXYGEN_SHOULD_SKIP_THIS
179
180    !---------------------------------------------------------------------------
181
182    ! Interface to C function retrieving pointers to members of the
183    ! global physical model flags
184
185    subroutine cs_f_fuel_get_pointers(p_nclafu)                                &
186      bind(C, name='cs_f_fuel_get_pointers')
187      use, intrinsic :: iso_c_binding
188      implicit none
189      type(c_ptr), intent(out) :: p_nclafu
190    end subroutine cs_f_fuel_get_pointers
191
192    !---------------------------------------------------------------------------
193
194    !> (DOXYGEN_SHOULD_SKIP_THIS) \endcond
195
196    !---------------------------------------------------------------------------
197
198  end interface
199
200  !=============================================================================
201
202contains
203
204  !=============================================================================
205
206  !> \brief Initialize Fortran combustion models properties API.
207  !> This maps Fortran pointers to global C variables.
208
209  subroutine fuel_models_init
210
211    use, intrinsic :: iso_c_binding
212    implicit none
213
214    ! Local variables
215
216    type(c_ptr) :: p_nclafu
217
218    call cs_f_fuel_get_pointers(p_nclafu)
219
220    call c_f_pointer(p_nclafu, nclafu)
221
222
223  end subroutine fuel_models_init
224
225  !=============================================================================
226
227end module cs_fuel_incl
228