Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ModInterfacesMixt.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: set explicit interfaces to subroutines and functions
26 ! related to the gas mixture.
27 !
28 ! Description: none
29 !
30 ! Notes: none.
31 !
32 !******************************************************************************
33 !
34 ! $Id: ModInterfacesMixt.F90,v 1.9 2008/12/06 08:44:18 mtcampbe Exp $
35 !
36 ! Copyright: (c) 2001 by the University of Illinois
37 !
38 !******************************************************************************
39 
41 
42  IMPLICIT NONE
43 
44  INTERFACE
45 
46  FUNCTION mixtgasliq_c(Cvm,D,P,Dl,Dv,Dg,VFl,VFv,VFg,Cl2,Cv2,Cg2,Bl2,Bv2,Bg2)
47  USE moddatatypes
48  REAL(RFREAL), INTENT(IN) :: bg2,bl2,bv2,cl2,cv2,cg2,cvm,d,dg,dl,dv,p,vfg,vfl,vfv
49  REAL(RFREAL) :: mixtgasliq_c
50  REAL(RFREAL) :: denom,numer,term1,term2,term3
51  END FUNCTION mixtgasliq_c
52 
53  FUNCTION mixtgasliq_eo_cvmtvm2(Cvm,T,Vm2)
54  USE moddatatypes
55  REAL(RFREAL), INTENT(IN) :: cvm,t,vm2
56  REAL(RFREAL) :: mixtgasliq_eo_cvmtvm2
57  END FUNCTION mixtgasliq_eo_cvmtvm2
58 
59  FUNCTION mixtgasliq_p(DYl,DYv,DYg,Cl2,Cv2,Cg2,D,Do,Po,To,Bp,Bt,T)
60  USE moddatatypes
61  REAL(RFREAL), INTENT(IN) :: bp,bt,cg2,cl2,cv2,d,do,dyg,dyl,dyv,po,t,to
62  REAL(RFREAL) :: mixtgasliq_p
63  REAL(RFREAL) :: term1,term2
64  END FUNCTION mixtgasliq_p
65 
66  FUNCTION mixtliq_c_bp(Bp)
67  USE moddatatypes
68  REAL(RFREAL), INTENT(IN) :: bp
69  REAL(RFREAL) :: mixtliq_c_bp
70  END FUNCTION mixtliq_c_bp
71 
72  FUNCTION mixtliq_c2_bp(Bp)
73  USE moddatatypes
74  REAL(RFREAL), INTENT(IN) :: bp
75  REAL(RFREAL) :: mixtliq_c2_bp
76  END FUNCTION mixtliq_c2_bp
77 
78  FUNCTION mixtliq_d_dobpppobttto(Do,Bp,Bt,P,Po,T,To)
79  USE moddatatypes
80  REAL(RFREAL), INTENT(IN) :: bp,bt,do,p,po,t,to
81  REAL(RFREAL) :: mixtliq_d_dobpppobttto
82  END FUNCTION mixtliq_d_dobpppobttto
83 
84  FUNCTION mixtperf_c_co2guvw( Co2,G,U,V,W )
85  USE moddatatypes
86  REAL(RFREAL), INTENT(IN) :: co2, g, u, v, w
87  REAL(RFREAL) :: mixtperf_c_co2guvw
88  END FUNCTION mixtperf_c_co2guvw
89 
90  FUNCTION mixtperf_c_dgp( D,G,P )
91  USE moddatatypes
92  REAL(RFREAL), INTENT(IN) :: d, g, p
93  REAL(RFREAL) :: mixtperf_c_dgp
94  END FUNCTION mixtperf_c_dgp
95 
96  FUNCTION mixtperf_c_ghovm2( G,Ho,Vm2 )
97  USE moddatatypes
98  REAL(RFREAL), INTENT(IN) :: g, ho, vm2
99  REAL(RFREAL) :: mixtperf_c_ghovm2
100  END FUNCTION mixtperf_c_ghovm2
101 
102  FUNCTION mixtperf_c_grt( G,R,T )
103  USE moddatatypes
104  REAL(RFREAL), INTENT(IN) :: g, r, t
105  REAL(RFREAL) :: mixtperf_c_grt
106  END FUNCTION mixtperf_c_grt
107 
108  FUNCTION mixtperf_co2_cguvw( C,G,U,V,W )
109  USE moddatatypes
110  REAL(RFREAL), INTENT(IN) :: c, g, u, v, w
111  REAL(RFREAL) :: mixtperf_co2_cguvw
112  END FUNCTION mixtperf_co2_cguvw
113 
114  FUNCTION mixtperf_c2_grt( G,R,T )
115  USE moddatatypes
116  REAL(RFREAL), INTENT(IN) :: g, r, t
117  REAL(RFREAL) :: mixtperf_c2_grt
118  END FUNCTION mixtperf_c2_grt
119 
120  FUNCTION mixtperf_cv_cpr( Cp,R )
121  USE moddatatypes
122  REAL(RFREAL), INTENT(IN) :: cp, r
123  REAL(RFREAL) :: mixtperf_cv_cpr
124  END FUNCTION mixtperf_cv_cpr
125 
126  FUNCTION mixtperf_d_cgp( C,G,P )
127  USE moddatatypes
128  REAL(RFREAL), INTENT(IN) :: c, g, p
129  REAL(RFREAL) :: mixtperf_d_cgp
130  END FUNCTION mixtperf_d_cgp
131 
132  FUNCTION mixtperf_d_dogma(Do,G,Ma)
133  USE moddatatypes
134  REAL(RFREAL), INTENT(IN) :: do,g,ma
135  REAL(RFREAL) :: mixtperf_d_dogma
136  END FUNCTION mixtperf_d_dogma
137 
138  FUNCTION mixtperf_d_prt( P,R,T )
139  USE moddatatypes
140  REAL(RFREAL), INTENT(IN) :: p, r ,t
141  REAL(RFREAL) :: mixtperf_d_prt
142  END FUNCTION mixtperf_d_prt
143 
144  FUNCTION mixtperf_eo_dgpuvw( D,G,P,U,V,W )
145  USE moddatatypes
146  REAL(RFREAL), INTENT(IN) :: d, g, p, u, v, w
147  REAL(RFREAL) :: mixtperf_eo_dgpuvw
148  END FUNCTION mixtperf_eo_dgpuvw
149 
150  FUNCTION mixtperf_eo_dgpvm( D,G,P,Vm )
151  USE moddatatypes
152  REAL(RFREAL), INTENT(IN) :: d, g, p ,vm
153  REAL(RFREAL) :: mixtperf_eo_dgpvm
154  END FUNCTION mixtperf_eo_dgpvm
155 
156  FUNCTION mixtperf_eo_grtuvw( G,R,T,U,V,W )
157  USE moddatatypes
158  REAL(RFREAL), INTENT(IN) :: g, r, t, u, v, w
159  REAL(RFREAL) :: mixtperf_eo_grtuvw
160  END FUNCTION mixtperf_eo_grtuvw
161 
162  FUNCTION mixtperf_g_cpr( Cp,R )
163  USE moddatatypes
164  REAL(RFREAL), INTENT(IN) :: cp, r
165  REAL(RFREAL) :: mixtperf_g_cpr
166  END FUNCTION mixtperf_g_cpr
167 
168  FUNCTION mixtperf_ho_cptuvw( Cp,T,U,V,W )
169  USE moddatatypes
170  REAL(RFREAL), INTENT(IN) :: cp, t, u, v, w
171  REAL(RFREAL) :: mixtperf_ho_cptuvw
172  END FUNCTION mixtperf_ho_cptuvw
173 
174  FUNCTION mixtperf_m_r( R )
175  USE moddatatypes
176  REAL(RFREAL), INTENT(IN) :: r
177  REAL(RFREAL) :: mixtperf_m_r
178  END FUNCTION mixtperf_m_r
179 
180  FUNCTION mixtperf_p_deogvm2( D,Eo,G,Vm2 )
181  USE moddatatypes
182  REAL(RFREAL), INTENT(IN) :: d, eo, g, vm2
183  REAL(RFREAL) :: mixtperf_p_deogvm2
184  END FUNCTION mixtperf_p_deogvm2
185 
186  FUNCTION mixtperf_p_drt(D,R,T)
187  USE moddatatypes
188  REAL(RFREAL), INTENT(IN) :: d,r,t
189  REAL(RFREAL) :: mixtperf_p_drt
190  END FUNCTION mixtperf_p_drt
191 
192  FUNCTION mixtperf_p_gmapo( G,Ma,Po )
193  USE moddatatypes
194  REAL(RFREAL), INTENT(IN) :: g, ma, po
195  REAL(RFREAL) :: mixtperf_p_gmapo
196  END FUNCTION mixtperf_p_gmapo
197 
198  FUNCTION mixtperf_p_ddogpo(G,Po,D,Do)
199  USE moddatatypes
200  REAL(RFREAL), INTENT(IN) :: d,do,g,po
201  REAL(RFREAL) :: mixtperf_p_ddogpo
202  END FUNCTION mixtperf_p_ddogpo
203 
204  FUNCTION mixtperf_p_gpotto( G,Po,T,To )
205  USE moddatatypes
206  REAL(RFREAL), INTENT(IN) :: g, po, t, to
207  REAL(RFREAL) :: mixtperf_p_gpotto
208  END FUNCTION mixtperf_p_gpotto
209 
210  FUNCTION mixtperf_po_gptto( G,P,T,To )
211  USE moddatatypes
212  REAL(RFREAL), INTENT(IN) :: g, p, t, to
213  REAL(RFREAL) :: mixtperf_po_gptto
214  END FUNCTION mixtperf_po_gptto
215 
216  FUNCTION mixtperf_po_cgpuvw( C,G,P,U,V,W )
217  USE moddatatypes
218  REAL(RFREAL), INTENT(IN) :: c, g, p, u, v, w
219  REAL(RFREAL) :: mixtperf_po_cgpuvw
220  END FUNCTION mixtperf_po_cgpuvw
221 
222  FUNCTION mixtperf_r_cpg( Cp,G )
223  USE moddatatypes
224  REAL(RFREAL), INTENT(IN) :: cp, g
225  REAL(RFREAL) :: mixtperf_r_cpg
226  END FUNCTION mixtperf_r_cpg
227 
228  FUNCTION mixtperf_r_m( M )
229  USE moddatatypes
230  REAL(RFREAL), INTENT(IN) :: m
231  REAL(RFREAL) :: mixtperf_r_m
232  END FUNCTION mixtperf_r_m
233 
234  FUNCTION mixtperf_t_cgr( C,G,R )
235  USE moddatatypes
236  REAL(RFREAL), INTENT(IN) :: c, g, r
237  REAL(RFREAL) :: mixtperf_t_cgr
238  END FUNCTION mixtperf_t_cgr
239 
240  FUNCTION mixtperf_t_cphovm2(Cp,Ho,Vm2)
241  USE moddatatypes
242  REAL(RFREAL), INTENT(IN) :: cp,ho,vm2
243  REAL(RFREAL) :: mixtperf_t_cphovm2
244  END FUNCTION mixtperf_t_cphovm2
245 
246  FUNCTION mixtperf_t_cveovm2(Cv,Eo,Vm2)
247  USE moddatatypes
248  REAL(RFREAL), INTENT(IN) :: cv,eo,vm2
249  REAL(RFREAL) :: mixtperf_t_cveovm2
250  END FUNCTION mixtperf_t_cveovm2
251 
252  FUNCTION mixtperf_t_dpr( D,P,R )
253  USE moddatatypes
254  REAL(RFREAL), INTENT(IN) :: d, p, r
255  REAL(RFREAL) :: mixtperf_t_dpr
256  END FUNCTION mixtperf_t_dpr
257 
258  FUNCTION mixtperf_t_gmato( G,Ma,To )
259  USE moddatatypes
260  REAL(RFREAL), INTENT(IN) :: g, ma, to
261  REAL(RFREAL) :: mixtperf_t_gmato
262  END FUNCTION mixtperf_t_gmato
263 
264  FUNCTION mixtperf_to_cptuvw(Cp,T,U,V,W)
265  USE moddatatypes
266  REAL(RFREAL), INTENT(IN) :: cp,t,u,v,w
267  REAL(RFREAL) :: mixtperf_to_cptuvw
268  END FUNCTION mixtperf_to_cptuvw
269 
270  FUNCTION mixtperf_vm_c2co2g( C2,Co2,G )
271  USE moddatatypes
272  REAL(RFREAL), INTENT(IN) :: c2, co2, g
273  REAL(RFREAL) :: mixtperf_vm_c2co2g
274  END FUNCTION mixtperf_vm_c2co2g
275 
276  SUBROUTINE mixtureproperties( region,inBeg,inEnd,gasUpdate )
277  USE moddatastruct, ONLY : t_region
278  INTEGER :: inbeg, inend
279  LOGICAL :: gasupdate
280  TYPE(t_region) :: region
281  END SUBROUTINE mixtureproperties
282 
283  SUBROUTINE perfgasdependentvars( inBeg,inEnd,indCp,indMol,cv,gv,dv )
284  USE moddatatypes
285  INTEGER :: inbeg, inend, indcp, indmol
286  REAL(RFREAL), POINTER :: cv(:,:), gv(:,:), dv(:,:)
287  END SUBROUTINE perfgasdependentvars
288 
289  SUBROUTINE perfgasgasvars( inBeg,inEnd,indCp,indMol,refCp,refGamma,cv,gv )
290  USE moddatatypes
291  INTEGER :: inbeg, inend, indcp, indmol
292  REAL(RFREAL) :: refcp, refgamma
293  REAL(RFREAL), POINTER :: cv(:,:), gv(:,:)
294  END SUBROUTINE perfgasgasvars
295 
296  SUBROUTINE perfgastransportvars( inBeg,inEnd,indCp,indMol,viscModel,prLam, &
297  refvisc,reftemp,suthcoef,cv,dv,gv,tv )
298  USE moddatatypes
299  INTEGER :: inbeg, inend, indcp, indmol, viscmodel
300  REAL(RFREAL) :: prlam, reftemp, refvisc, suthcoef
301  REAL(RFREAL), POINTER :: cv(:,:), dv(:,:), gv(:,:), tv(:,:)
302  END SUBROUTINE perfgastransportvars
303 
304  END INTERFACE
305 
306 END MODULE modinterfacesmixt
307 
308 !******************************************************************************
309 !
310 ! RCS Revision history:
311 !
312 ! $Log: ModInterfacesMixt.F90,v $
313 ! Revision 1.9 2008/12/06 08:44:18 mtcampbe
314 ! Updated license.
315 !
316 ! Revision 1.8 2008/11/19 22:17:30 mtcampbe
317 ! Added Illinois Open Source License/Copyright
318 !
319 ! Revision 1.7 2006/05/01 21:03:25 haselbac
320 ! Added if for MixtPerf_T_CpHoVm2
321 !
322 ! Revision 1.6 2006/03/26 20:21:54 haselbac
323 ! Added ifs for new routines
324 !
325 ! Revision 1.5 2005/07/14 21:40:52 haselbac
326 ! Added interface for MixtPerf_To_CpTUVW
327 !
328 ! Revision 1.4 2005/03/15 20:43:45 haselbac
329 ! Added interface for MixtPerf_D_CGP
330 !
331 ! Revision 1.3 2004/04/01 21:28:41 haselbac
332 ! Added entry for MixtPerf_E_GRTUVW
333 !
334 ! Revision 1.2 2003/09/16 15:04:35 haselbac
335 ! Added interfaces for new MixtPerf functions
336 !
337 ! Revision 1.1 2003/08/11 21:50:00 jblazek
338 ! Splitted ModInterfaces into 4 sections.
339 !
340 !******************************************************************************
341 
342 
343 
344 
345 
346 
real(rfreal) function mixtperf_eo_dgpvm(D, G, P, Vm)
Definition: MixtPerf_E.F90:55
unsigned char r() const
Definition: Color.h:68
FT m(int i, int j) const
real(rfreal) function mixtperf_p_deogvm2(D, Eo, G, Vm2)
Definition: MixtPerf_P.F90:39
real(rfreal) function mixtperf_r_m(M)
Definition: MixtPerf_R.F90:54
subroutine perfgasdependentvars(inBeg, inEnd, indCp, indMol, cv, gv, dv)
const NT & d
real(rfreal) function mixtperf_c_dgp(D, G, P)
Definition: MixtPerf_C.F90:56
real(rfreal) function mixtperf_t_cgr(C, G, R)
Definition: MixtPerf_T.F90:40
real(rfreal) function mixtperf_po_cgpuvw(C, G, P, U, V, W)
Definition: MixtPerf_P.F90:130
real(rfreal) function mixtperf_p_ddogpo(D, Do, G, Po)
Definition: MixtPerf_P.F90:85
real(rfreal) function mixtperf_d_prt(P, R, T)
Definition: MixtPerf_D.F90:71
real(rfreal) function mixtperf_vm_c2co2g(C2, Co2, G)
Definition: MixtPerf_Vm.F90:39
real(rfreal) function mixtperf_c_ghovm2(G, Ho, Vm2)
Definition: MixtPerf_C.F90:71
real(rfreal) function mixtperf_r_cpg(Cp, G)
Definition: MixtPerf_R.F90:39
RT c() const
Definition: Line_2.h:150
real(rfreal) function mixtgasliq_p(DYl, DYv, DYg, Cl2, Cv2, Cg2, D, Dz, Po, To, Bp, Bt, T)
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **ARISING OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE v
Definition: roccomf90.h:20
real(rfreal) function mixtliq_c_bp(Bp)
Definition: MixtLiq_C.F90:39
real(rfreal) function mixtperf_c_co2guvw(Co2, G, U, V, W)
Definition: MixtPerf_C.F90:40
real(rfreal) function mixtperf_c2_grt(G, R, T)
Definition: MixtPerf_C.F90:101
real(rfreal) function mixtperf_ho_cptuvw(Cp, T, U, V, W)
Definition: MixtPerf_H.F90:39
real(rfreal) function mixtperf_t_cphovm2(Cp, Ho, Vm2)
Definition: MixtPerf_T.F90:55
real(rfreal) function mixtliq_c2_bp(Bp)
Definition: MixtLiq_C.F90:54
real(rfreal) function mixtperf_m_r(R)
Definition: MixtPerf_M.F90:39
real(rfreal) function mixtperf_d_cgp(C, G, P)
Definition: MixtPerf_D.F90:40
real(rfreal) function mixtperf_po_gptto(G, P, T, To)
Definition: MixtPerf_P.F90:115
real(rfreal) function mixtperf_t_dpr(D, P, R)
Definition: MixtPerf_T.F90:85
real(rfreal) function mixtperf_d_dogma(Do, G, Ma)
Definition: MixtPerf_D.F90:55
real(rfreal) function mixtgasliq_eo_cvmtvm2(Cvm, T, Vm2)
real(rfreal) function mixtliq_d_dobpppobttto(Dz, Bp, Bt, P, Po, T, To)
Definition: MixtLiq_D.F90:40
real(rfreal) function mixtperf_c_grt(G, R, T)
Definition: MixtPerf_C.F90:86
real(rfreal) function mixtgasliq_c(Cvm, D, P, Dl, Dv, Dg, VFl, VFv, VFg, Cl2, Cv2, Cg2, Bl2, Bv2, Bg2)
real(rfreal) function mixtperf_t_gmato(G, Ma, To)
Definition: MixtPerf_T.F90:100
real(rfreal) function mixtperf_eo_dgpuvw(D, G, P, U, V, W)
Definition: MixtPerf_E.F90:40
real(rfreal) function mixtperf_co2_cguvw(C, G, U, V, W)
Definition: MixtPerf_C.F90:116
subroutine perfgastransportvars(inBeg, inEnd, indCp, indMol, viscModel, prLam, refVisc, refTemp, suthCoef, cv, dv, gv, tv)
subroutine perfgasgasvars(inBeg, inEnd, indCp, indMol, refCp, refGamma, cv, gv)
subroutine mixtureproperties(region, inBeg, inEnd, gasUpdate)
real(rfreal) function mixtperf_t_cveovm2(Cv, Eo, Vm2)
Definition: MixtPerf_T.F90:70
real(rfreal) function mixtperf_p_gpotto(G, Po, T, To)
Definition: MixtPerf_P.F90:100
real(rfreal) function mixtperf_to_cptuvw(Cp, T, U, V, W)
Definition: MixtPerf_T.F90:115
real(rfreal) function mixtperf_g_cpr(Cp, R)
Definition: MixtPerf_G.F90:39
CGAL_BEGIN_NAMESPACE void const NT NT NT NT & denom
real(rfreal) function mixtperf_eo_grtuvw(G, R, T, U, V, W)
Definition: MixtPerf_E.F90:70
real(rfreal) function mixtperf_cv_cpr(Cp, R)
Definition: MixtPerf_Cv.F90:39
real(rfreal) function mixtperf_p_drt(D, R, T)
Definition: MixtPerf_P.F90:54
unsigned char g() const
Definition: Color.h:69
real(rfreal) function mixtperf_p_gmapo(G, Ma, Po)
Definition: MixtPerf_P.F90:69