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 ppthch.f90
24!> Module for specific physics thermophysical data
25
26module ppthch
27
28  !===========================================================================
29
30  use, intrinsic :: iso_c_binding
31
32  use cstphy
33
34  implicit none
35
36  !===========================================================================
37
38  !> \defgroup  thermophysical Module for specific physics thermophysical data
39
40  !> \addtogroup thermophysical
41  !> \{
42
43  !> reference temperature for the specific physics, in K
44  double precision trefth
45
46  !> reference pressure for the specific physics, in Pa
47  double precision prefth
48
49  !> molar volume under normal pressure and temperature conditions
50  !>  (1 atmosphere, 0 \f$\text{\degresC}\f$) in \f$m^{-3}\f$
51  double precision volmol
52
53  parameter ( trefth = 25.d0 + tkelvi ,                             &
54              prefth = 1.01325d5      ,                             &
55              volmol = 22.41d-3       )
56
57  !--> DONNEES
58
59  !> maximal number of global species
60  integer    ngazgm
61
62  !> maximal number of elementary gas components
63  integer    ngazem
64
65  !> maximal number of tabulation points
66  integer    npot
67
68  !> maximal number of atomic species
69  integer    natom
70
71  !> maximal number of global reactions in gas phase
72  integer    nrgazm
73
74  parameter( ngazgm = 25 , ngazem = 20 ,                                     &
75             npot  = 500 , natom  = 5   , nrgazm = 1 )
76  integer    iatc, iath, iato, iatn , iats
77  parameter( iatc = 1, iath = 2, iato = 3, iatn = 4 , iats = 5 )
78
79  !> name of global species
80  character(len=150) :: nomcog(ngazgm)
81  !> name of elementary species
82  character(len=12) :: nomcoe(ngazem)
83
84  !> number of tabulation points
85  integer, save ::           npo
86
87  !> number of elementary gas components
88  integer, pointer, save ::  ngaze
89  !> number of global species
90  integer, pointer, save ::  ngazg
91  !> number of atomic species
92  integer, pointer, save ::  nato
93
94  !> number of global reactions in gas phase
95  integer, pointer, save ::  nrgaz
96
97  !> rank of O2 in gas composition
98  integer, save ::           iio2
99  !> rank of H2O in gas composition
100  integer, save ::           iih2o
101  !> rank of CO2 in gas composition
102  integer, save ::           iico2
103  !> rank of CO in gas composition
104  integer, save ::           iico
105  !> rank of C in gas composition
106  integer, pointer, save ::  iic
107
108  !> rank of fuel in the r-th reaction
109  integer, save ::           igfuel(nrgazm)
110  !> rank of oxydiser in the r-th reaction
111  integer, save ::           igoxy(nrgazm)
112  !> rank of products in the r-th reaction
113  integer, save ::           igprod(nrgazm)
114
115  !> stoechiometric coefficient of global species
116  double precision, save ::  nreact(ngazgm)
117
118  !> temperature (in K)
119  double precision, save ::  th(npot)
120
121  !> engaze(ij) is the massic enthalpy (J/kg) of the i-th elementary gas component
122  !> at temperature  th(j)
123  double precision, save ::  ehgaze(ngazem,npot)
124
125  !> engazg(ij) is the massic enthalpy (J/kg) of the i-th global secies
126  !> at temperature  th(j)
127  double precision, save ::  ehgazg(ngazgm,npot)
128
129  !> cpgazg(ij) is the massic calorific capacity (J/kg/K) of the i-th global secies
130  !> at temperature  th(j)
131  double precision, save ::  cpgazg(ngazgm,npot)
132
133  !> molar mass of an elementary gas component
134  real(c_double), pointer, save ::  wmole(:)
135
136  !> molar mass of a global species
137  real(c_double), pointer, save ::  wmolg(:)
138
139  !> molar mass of atoms
140  double precision, save ::  wmolat(natom)
141
142  !> Stoichiometry in reaction global species.  Negative for the reactants,
143  !> and positive for the products
144  double precision, save ::  stoeg(ngazgm,nrgazm)
145
146  !> Mixing rate at the stoichiometry
147  double precision, save ::  fs(nrgazm)
148
149  !> Absorption coefficient of global species
150  double precision, save ::  ckabsg(ngazgm)
151
152  !> Absorption coefficient of gas mixture
153  real(c_double), pointer, save ::  ckabs1
154
155  !> \anchor diftl0
156  !> molecular diffusivity for the enthalpy (\f$kg.m^{-1}.s^{-1}\f$)
157  !> for gas or coal combustion (the code then automatically sets
158  !> \ref diffusivity_ref to \ref diftl0 for the scalar
159  !> representing the enthalpy).
160  !>
161  !> Always useful for gas or coal combustion.
162  double precision, save ::  diftl0
163
164  !> Molar coefficient of CO2
165  real(c_double), pointer, save ::  xco2
166  !> Molar coefficient of H2O
167  real(c_double), pointer, save ::  xh2o
168
169  !=============================================================================
170
171  !> \}
172
173  !=============================================================================
174
175  interface
176
177    !---------------------------------------------------------------------------
178
179    !> \cond DOXYGEN_SHOULD_SKIP_THIS
180
181    !---------------------------------------------------------------------------
182
183    ! Interface to C function retrieving pointers to members of the
184    ! global physical model flags
185
186    subroutine cs_f_ppthch_get_pointers(p_ngaze, p_ngazg, p_nato, p_nrgaz,  &
187                                        p_iic, p_wmole, p_wmolg,            &
188                                        p_xco2, p_xh2o, p_ckabs1)           &
189      bind(C, name='cs_f_ppthch_get_pointers')
190      use, intrinsic :: iso_c_binding
191      implicit none
192      type(c_ptr), intent(out) :: p_ngaze, p_ngazg, p_nato, p_nrgaz, p_iic,    &
193                                  p_wmolg, p_wmole, p_xco2, p_xh2o, p_ckabs1
194    end subroutine cs_f_ppthch_get_pointers
195
196    !---------------------------------------------------------------------------
197
198    !> (DOXYGEN_SHOULD_SKIP_THIS) \endcond
199
200    !---------------------------------------------------------------------------
201
202  end interface
203
204  !=============================================================================
205
206contains
207
208  !=============================================================================
209
210  !> \brief Initialize Fortran combustion models properties API.
211  !> This maps Fortran pointers to global C variables.
212
213  subroutine thch_models_init
214
215    use, intrinsic :: iso_c_binding
216    implicit none
217
218    ! Local variables
219
220    type(c_ptr) :: p_ngaze, p_ngazg, p_nato, p_nrgaz, p_iic
221    type(c_ptr) :: p_wmole, p_wmolg, p_xco2, p_xh2o, p_ckabs1
222
223    call cs_f_ppthch_get_pointers(p_ngaze, p_ngazg, p_nato, p_nrgaz, p_iic,  &
224                                  p_wmole, p_wmolg,                          &
225                                  p_xco2, p_xh2o, p_ckabs1)
226
227    call c_f_pointer(p_ngaze, ngaze)
228    call c_f_pointer(p_ngazg, ngazg)
229    call c_f_pointer(p_nato, nato)
230    call c_f_pointer(p_nrgaz, nrgaz)
231    call c_f_pointer(p_iic, iic)
232    call c_f_pointer(p_wmole, wmole, [ngazem])
233    call c_f_pointer(p_wmolg, wmolg, [ngazgm])
234    call c_f_pointer(p_xco2, xco2)
235    call c_f_pointer(p_xh2o, xh2o)
236    call c_f_pointer(p_ckabs1, ckabs1)
237
238  end subroutine thch_models_init
239
240  !=============================================================================
241
242end module ppthch
243