CFD Online Logo CFD Online URL
www.cfd-online.com
[Sponsors]
Home > Forums > Software User Forums > ANSYS > CFX

anyone know the problem of my cavitation flow?

Register Blogs Members List Search Today's Posts Mark Forums Read

Reply
 
LinkBack Thread Tools Search this Thread Display Modes
Old   August 2, 2011, 12:35
Default anyone know the problem of my cavitation flow?
  #1
New Member
 
GARY JANE
Join Date: Nov 2010
Posts: 11
Rep Power: 15
alloveyou is on a distinguished road
The problem is like that:when i set the saturation pressure as constant in the cavitation,it's fine,but if i set the pressure as the function of temperature ,it always made an error below:

Slave: 2
Slave: 2 Details of error:-
Slave: 2 ----------------
Slave: 2 Error detected by routine MAKDAT
Slave: 2 CDANAM = PSATREL CDTYPE = REAL ISIZE = 903
Slave: 2 CRESLT = OLD
Slave: 2
Slave: 2 Current Directory : /FLOW/PHYSICS/MATERIALS/MT2/ENTHSTAT
.
.
.
+--------------------------------------------------------------------+
| ERROR #001100279 has occurred in subroutine ErrAction. |
| Message: |
| Stopped in routine MEMERR |
| |
| |
| |
| |
| |
+--------------------------------------------------------------------+
anyone know the problem and how to solve it?
Thank you very much!
alloveyou is offline   Reply With Quote

Old   August 29, 2011, 18:31
Default
  #2
New Member
 
Join Date: Aug 2011
Posts: 8
Rep Power: 14
congtuha is on a distinguished road
Quote:
Originally Posted by alloveyou View Post
The problem is like that:when i set the saturation pressure as constant in the cavitation,it's fine,but if i set the pressure as the function of temperature ,it always made an error below:

Slave: 2
Slave: 2 Details of error:-
Slave: 2 ----------------
Slave: 2 Error detected by routine MAKDAT
Slave: 2 CDANAM = PSATREL CDTYPE = REAL ISIZE = 903
Slave: 2 CRESLT = OLD
Slave: 2
Slave: 2 Current Directory : /FLOW/PHYSICS/MATERIALS/MT2/ENTHSTAT
.
.
.
+--------------------------------------------------------------------+
| ERROR #001100279 has occurred in subroutine ErrAction. |
| Message: |
| Stopped in routine MEMERR |
| |
| |
| |
| |
| |
+--------------------------------------------------------------------+
anyone know the problem and how to solve it?
Thank you very much!
You should check if the temperature and pressure of your solution are in the range of valid or not. Take a look at the standard for the thermodynamic properties of water over a wide range of temperature and pressure which is provided by the IAPWS Industrial Formulation 1997. The link to download is:
http://www.cheresources.com/content/...ater-and-steam
I have also worked on the compressible cavitating flows. If you want to use my subroutine developed for IAPWS-IF97 just tell me.
congtuha is offline   Reply With Quote

Old   August 29, 2011, 19:34
Default
  #3
Super Moderator
 
Glenn Horrocks
Join Date: Mar 2009
Location: Sydney, Australia
Posts: 17,665
Rep Power: 143
ghorrocks is just really niceghorrocks is just really niceghorrocks is just really niceghorrocks is just really nice
Why not use the built-in IAPWS water properties?
ghorrocks is offline   Reply With Quote

Old   August 30, 2011, 01:58
Default
  #4
New Member
 
Join Date: Aug 2011
Posts: 8
Rep Power: 14
congtuha is on a distinguished road
Quote:
Originally Posted by ghorrocks View Post
Why not use the built-in IAPWS water properties?
Do you think it is a good way to use the built-in in your fortran code?
congtuha is offline   Reply With Quote

Old   August 30, 2011, 07:11
Default
  #5
Super Moderator
 
Glenn Horrocks
Join Date: Mar 2009
Location: Sydney, Australia
Posts: 17,665
Rep Power: 143
ghorrocks is just really niceghorrocks is just really niceghorrocks is just really niceghorrocks is just really nice
I do not understand your point. The IAPWS water properties are already available in CFX so you do not need to code anything in fortran to get them. It is available through the GUI. But I guess it is good fortran training
ghorrocks is offline   Reply With Quote

Old   May 15, 2012, 01:18
Default flash boiling flows
  #6
New Member
 
SV
Join Date: May 2012
Posts: 2
Rep Power: 0
s3336481 is on a distinguished road
Quote:
Originally Posted by congtuha View Post
You should check if the temperature and pressure of your solution are in the range of valid or not. Take a look at the standard for the thermodynamic properties of water over a wide range of temperature and pressure which is provided by the IAPWS Industrial Formulation 1997. The link to download is:
http://www.cheresources.com/content/...ater-and-steam
I have also worked on the compressible cavitating flows. If you want to use my subroutine developed for IAPWS-IF97 just tell me.
Hi congtuha,

I am modelling flash boiling flows in CFX. I wonder if I could have your subroutine developed for IAPWS-IF97?

Thanks in advance
s3336481 is offline   Reply With Quote

Old   May 15, 2012, 08:42
Default
  #7
Super Moderator
 
Glenn Horrocks
Join Date: Mar 2009
Location: Sydney, Australia
Posts: 17,665
Rep Power: 143
ghorrocks is just really niceghorrocks is just really niceghorrocks is just really niceghorrocks is just really nice
Um - did you read my posts? You do not need to code IAPWS-97 as it is already in CFX. If you have time to waste then feel free to code it up but I have better things to do with my time.
ghorrocks is offline   Reply With Quote

Old   May 15, 2012, 16:55
Default
  #8
New Member
 
SV
Join Date: May 2012
Posts: 2
Rep Power: 0
s3336481 is on a distinguished road
Quote:
Originally Posted by ghorrocks View Post
Um - did you read my posts? You do not need to code IAPWS-97 as it is already in CFX. If you have time to waste then feel free to code it up but I have better things to do with my time.
Hi ghorrocks,

Thanks for your comment. I thought the mentioned code in previous posts is modification of IAPWS-IF97 which can model "metastable state" present during the cavitation and flash boiling. So the built-in IAPWS is accurate enough to model "metastable state" ?
s3336481 is offline   Reply With Quote

Old   May 15, 2012, 20:38
Default
  #9
Super Moderator
 
Glenn Horrocks
Join Date: Mar 2009
Location: Sydney, Australia
Posts: 17,665
Rep Power: 143
ghorrocks is just really niceghorrocks is just really niceghorrocks is just really niceghorrocks is just really nice
The IAPWS-97 model is pretty accurate in the metastable region and this is included in the CFX built in model.
ghorrocks is offline   Reply With Quote

Old   December 23, 2015, 07:16
Default
  #10
New Member
 
Join Date: Aug 2011
Posts: 8
Rep Power: 14
congtuha is on a distinguished road
Quote:
Originally Posted by s3336481 View Post
Hi congtuha,

I am modelling flash boiling flows in CFX. I wonder if I could have your subroutine developed for IAPWS-IF97?

Thanks in advance
Sorry. I have not visited this site for such a long time. Here, I'd give you the subroutines for calculations of water, vapor properties and their derivatives with respect to p and T under thermodynamic equilibrium assumptions:

SUBROUTINE CONSTANT
IMPLICIT NONE
REAL*8 CII1,CJI1,CNI1
REAL*8 CNI2,CNI6,CNI7,CNI9,CNIJ10,CNI11
REAL*8 CJI0,CNI0
REAL*8 CII4,CJI4,CNI4
REAL*8 CII5,CJI5,CNI5
REAL*8 CII8,CJI8,CNI8
COMMON/TAB1/CII1(34),CJI1(34),CNI1(34),CNI2(5),CJI0(9),CNI0(9) ,
& CII4(43),CJI4(43),CNI4(43),CII5(40),CJI5(40),CNI5( 40),
& CNI6(10),CNI7(4),CII8(19),CJI8(19),CNI8(19),CNI9(4 ),
& CNIJ10(6,5),CNI11(5)
INTEGER I

REAL*8 INDE(43)
OPEN(111,FILE='TABLES.DAT')
DO I=1,15
READ(111,*)
ENDDO
DO I=1,34
READ(111,*)INDE(I),CII1(I),CJI1(I),CNI1(I)
ENDDO
C READ TABLE 2
READ(111,*)
READ(111,*)
DO I=1,5
READ(111,*)INDE(I),CNI2(I)
ENDDO
C READ TABLE 3
READ(111,*)
READ(111,*)
DO I=1,9
READ(111,*)INDE(I),CJI0(I),CNI0(I)
ENDDO
C READ TABLE 4
READ(111,*)
READ(111,*)
DO I=1,43
READ(111,*)INDE(I),CII4(I),CJI4(I),CNI4(I)
ENDDO
C READ TABLE 5
READ(111,*)
READ(111,*)
DO I=1,40
READ(111,*)INDE(I),CII5(I),CJI5(I),CNI5(I)
ENDDO

C READ TABLE 6
READ(111,*)
READ(111,*)
DO I=1,10
READ(111,*)INDE(I),CNI6(I)
ENDDO
C READ TABLE 7
READ(111,*)
READ(111,*)
DO I=1,4
READ(111,*)INDE(I),CNI7(I)
ENDDO
C READ TABLE 8
READ(111,*)
READ(111,*)
DO I=1,19
READ(111,*)INDE(I),CII8(I),CJI8(I),CNI8(I)
ENDDO

C READ TABLE 9
READ(111,*)
READ(111,*)
DO I=1,4
READ(111,*)INDE(I),CNI9(I)
ENDDO
C READ TABLE 11
READ(111,*)
READ(111,*)
DO I=1,5
READ(111,*)INDE(I),CNI11(I)
ENDDO
C READ TABLE 10
READ(111,*)
READ(111,*)
DO I=1,6
READ(111,*)CNIJ10(I,1),CNIJ10(I,2),CNIJ10(I,3),CNI J10(I,4),CNIJ10(I,5)
ENDDO
CLOSE(111)
RETURN
END

SUBROUTINE PROP(YV,TNK,PPASL,PV,DROLP,DROLT,DHLP,DHLT,HLP,
& ROLP,DROVP,DROVT,DHVP,DHVT,HVP,ROVP,PSATP,TSATP,IF L,
& MULP,MUVP,CKLP,CKVP)
IMPLICIT NONE
REAL*8 CII1,CJI1,CNI1
REAL*8 CNI2,CNI6,CNI7,CNI9,CNIJ10,CNI11
REAL*8 CJI0,CNI0
REAL*8 CII4,CJI4,CNI4
REAL*8 CII5,CJI5,CNI5
REAL*8 CII8,CJI8,CNI8
COMMON/TAB1/CII1(34),CJI1(34),CNI1(34),CNI2(5),CJI0(9),CNI0(9) ,
& CII4(43),CJI4(43),CNI4(43),CII5(40),CJI5(40),CNI5( 40),
& CNI6(10),CNI7(4),CII8(19),CJI8(19),CNI8(19),CNI9(4 ),
& CNIJ10(6,5),CNI11(5)
REAL*8 TLIM1,TLIM2,TLIM3,TLIM4,TLIM5,R

PARAMETER (TLIM1=273.15D0,TLIM2=623.15D0,TLIM3=647.096D0)
PARAMETER (TLIM4=863.15D0,TLIM5=1073.15,R=461.526D0)
INTEGER II,IFL
REAL*8 DROLP,DROLT,DHLP,DHLT,HLP,ROLP,MULP,MUVP,CKLP,CKVP
REAL*8 DROVP,DROVT,DHVP,DHVT,HVP,ROVP,PSATP,PB23
REAL*8 PPASL,PPASV,TNK,TNKL,TNKV,TAUL,TAUV,TS,AAS,BBS,CCS ,PAIL,PAIV,
& GPI,GPIPI,GPITAU,GTAU,GTAUTAU,GTAUPI,GPIR,
& GPIPI0,GPIPIR,GPITAU1R,GTAU1R,GTAU1PI0,
& GTAU1PIR,GTTR,GTAU10,GTT0,YV,THETA
REAL*8 PP,BET,EES,FFS,GGS,DDS,TSATP,PV
PP=PPASL
PPASV=PPASL
TS=TNK;TNKL=TNK;TNKV=TNK
C COMPUTE SATURATION TEMPERATURE
C CHECK IF P IS OUTSITE THE VALID RANGE FOR REGION...
IF (PP.LT.611.212677D0)PP=611.212677D0
IF (PP.GT.22.064D6)PP=22.064D6
BET=(PP/1.D6)**0.25D0
EES=BET**2.D0+CNI6(3)*BET+CNI6(6)
FFS=CNI6(1)*BET**2.D0+CNI6(4)*BET+CNI6(7)
GGS=CNI6(2)*BET**2.D0+CNI6(5)*BET+CNI6(8)
DDS=2.D0*GGS/(-FFS-DSQRT(FFS**2.D0-4.D0*EES*GGS))
TSATP=0.5D0*(CNI6(10)+DDS-
& DSQRT( (CNI6(10)+DDS)**2.D0 -4.D0*(CNI6(9)+CNI6(10)*DDS) ) )
C COMPUTE SATURATION PRESSURE
C CHECK IF TS IS OUTSITE THE VALID RANGE FOR REGION 4
IF (TS.LT.TLIM1)TS=TLIM1
IF (TS.GT.TLIM2)TS=TLIM2
THETA=TS+CNI6(9)/(TS-CNI6(10))
AAS=THETA**2.D0+CNI6(1)*THETA+CNI6(2)
BBS=CNI6(3)*THETA**2.D0+CNI6(4)*THETA+CNI6(5)
CCS=CNI6(6)*THETA**2.D0+CNI6(7)*THETA+CNI6(8)
PSATP=1.0D+06*(2.D0*CCS/
1 (-BBS+DSQRT(BBS**2.D0-4.D0*AAS*CCS)))**4.D0

C COMPUTE BOILING PRESSURE
PB23=1.D6*(CNI11(1)+CNI11(2)*TNK+CNI11(3)*TNK**2.D 0)
C COMPUTE LIQUID AND VAPOR DENSITY
C CHECK IF TNKL AND PPASL ARE OUTSITE THE VALID RANGE FOR REGION 1
IF (TNKL.LT.TLIM1)TNKL=TLIM1
IF (TNKL.GT.TLIM2)TNKL=TLIM2

IF (PPASL.LT.PSATP)PPASL=PSATP
IF (PPASL.GT.1.0D8)PPASL=1.0D8

IF (YV.NE.0.D0) PPASL=PSATP
C CHECK IF TNKV AND PPASV ARE OUTSITE THE VALID RANGE FOR REGION 2
IF (TNKV.LT.TLIM1)TNKV=TLIM1
IF (TNKV.GT.TLIM5)TNKV=TLIM5
IF (YV.NE.1.D0.OR.PPASV.GT.PSATP)PPASV=PSATP
IF (TNKV.GT.TLIM2.AND.TNKV.LE.TLIM4.AND.PPASV.GT.PB23 )PPASV=PB23
IF (TNKV.GT.TLIM4.AND.TNKV.LE.TLIM5.AND.PPASV.GT.1.D8 )PPASV=1.D8
IF (PPASV.LT.611.212677D0) PPASV=611.212677D0

PAIL=PPASL/16.53D+06
PAIV=PPASV/1.0D+06
TAUL=1386.0D0/TNKL
TAUV=540.0D0/TNKV

C PARAMETERS FOR LIQUID
GPI =0.D0
GPIPI =0.D0
GPITAU =0.D0
GTAU =0.D0
GTAUTAU=0.D0
GTAUPI =0.D0
C PARAMETERS FOR VAPOR
GPIR =0.D0
GPIPI0 =-1.D0/PAIV**2.D0
GPIPIR =0.D0
GPITAU1R=0.D0
GTAU1R =0.D0
GTAU1PI0=0.D0
GTAU1PIR=0.D0
GTTR =0.D0
GTAU10 =0.D0
GTT0 =0.D0
DO II=1,43
IF (II.LE.34)THEN
C COMPUTE LIQUID DENSITY
GPI =GPI-CNI1(II)*CII1(II)*(7.1D0-PAIL)**(CII1(II)-1.D0)
& *(TAUL-1.222D0)**CJI1(II)
C COMPUTE DERIVATIVES OF LIQUID DENSITY WITH RESPECT TO P AND T
GPIPI =GPIPI+CNI1(II)*CII1(II)*(CII1(II)-1.D0)*(7.1D0-PAIL)**
& (CII1(II)-2.D0)*(TAUL-1.222D0)**CJI1(II)
GPITAU=GPITAU-CNI1(II)*CII1(II)*(7.1D0-PAIL)**(CII1(II)-1.D0)*
& CJI1(II)*(TAUL-1.222D0)**(CJI1(II)-1.D0)
C COMPUTE LIQUID ENTHALPY
GTAU =GTAU+CNI1(II)*(7.1D0-PAIL)**CII1(II)*
& CJI1(II)*(TAUL-1.222D0)**(CJI1(II)-1.D0)
C COMPUTE THE DERIVATIVES OF LIQUID ENTHALPY WITH RESPECT TO P AND T
GTAUTAU=GTAUTAU+CNI1(II)*(7.1D0-PAIL)**CII1(II)*CJI1(II)*
& (CJI1(II)-1.D0)*(TAUL-1.222D0)**(CJI1(II)-2.D0)

GTAUPI =GTAUPI-CNI1(II)*CII1(II)*(7.1D0-PAIL)**(CII1(II)-1.D0)*
& CJI1(II)*(TAUL-1.222D0)**(CJI1(II)-1.D0)
ENDIF !II<=34
IF (II.LE.9)THEN
GTAU10 =GTAU10+CNI0(II)*CJI0(II)*TAUV**(CJI0(II)-1.D0)
GTT0 =GTT0+CNI0(II)*CJI0(II)*(CJI0(II)-1.D0)*
& TAUV**(CJI0(II)-2.D0)
ENDIF !II<=9
GPIR =GPIR+CNI4(II)*CII4(II)*
& PAIV**(CII4(II)-1.D0)*(TAUV-0.5D0)**CJI4(II)
COMPUTE DERIVATIVES OF VAPOR DENSITY WITH RESPECTO P AND T
GPIPIR =GPIPIR +CNI4(II)*CII4(II)*(CII4(II)-1.D0)*
& PAIV**(CII4(II)-2.D0)*(TAUV-0.5D0)**CJI4(II)
GPITAU1R=GPITAU1R +CNI4(II)*CII4(II)*PAIV**(CII4(II)-1.D0)*
& CJI4(II)*(TAUV-0.5D0)**(CJI4(II)-1.D0)
GTAU1R=GTAU1R+CNI4(II)*PAIV**CII4(II)*
& CJI4(II)*(TAUV-0.5D0)**(CJI4(II)-1.D0)
C COMPUTE DERIVATIVES OD VAPOR ENTHALPY ABOUT P AND T : CPSATVAPTW(T)
GTAU1PIR=GTAU1PIR+CNI4(II)*CII4(II)*PAIV**(CII4(II )-1.D0)*
& CJI4(II)*(TAUV-0.5D0)**(CJI4(II)-1.D0) !!
GTTR=GTTR+CNI4(II)*PAIV**CII4(II)*CJI4(II)*
& (CJI4(II)-1.D0)*(TAUV-0.5D0)**(CJI4(II)-2.D0)
ENDDO

DROLP=-GPIPI/R/TNKL/GPI**2.D0
DROLT=-16.53D+06*(GPI-TAUL*GPITAU)/R/TNKL**2.D0/GPI**2.D0
DHLT=-TAUL**2.D0*R*GTAUTAU
DHLP=1386.0D0*R*GTAUPI/16.53D+06
ROLP=(R*TNKL*GPI/16.53D+06)**(-1.D0)
HLP=R*1386.0D0*GTAU

DROVP=-(GPIPI0+GPIPIR)/R/TNKV/(1.D0/PAIv+GPIR)**2.D0
DROVT=-1.0D+6/R/TNKV**2.D0*(1.D0/
1 (1.D0/PAIV+GPIR)-TAUV*GPITAU1R/(1.D0/PAIV+GPIR)**2.D0)
DHVP=R*540.D0/1.0D+06*(GTAU1PI0+GTAU1PIR)
DHVT=-R*TAUV**2.D0*(GTT0+GTTR)
ROVP=(R*TNKV/1.0D+06*(1.D0/PAIV+GPIR))**(-1.D0)
HVP=R*540.D0*(GTAU10+GTAU1R)
IF (IFL.EQ.1)CALL VISCOSITY(TNKL,TNKV,PPASL,PPASV,ROLP,ROVP,
& MULP,MUVP,CKLP,CKVP)
PPASL=PP; PV=PPASV
RETURN
END
SUBROUTINE VISCOSITY(TNKL,TNKV,PPASL,PPASV,ROLP,ROVP,
& MULP,MUVP,CKLP,CKVP)
IMPLICIT NONE
REAL*8 CII1,CJI1,CNI1
REAL*8 CNI2,CNI6,CNI7,CNI9,CNIJ10,CNI11
REAL*8 CJI0,CNI0
REAL*8 CII4,CJI4,CNI4
REAL*8 CII5,CJI5,CNI5
REAL*8 CII8,CJI8,CNI8
COMMON/TAB1/CII1(34),CJI1(34),CNI1(34),CNI2(5),CJI0(9),CNI0(9) ,
& CII4(43),CJI4(43),CNI4(43),CII5(40),CJI5(40),CNI5( 40),
& CNI6(10),CNI7(4),CII8(19),CJI8(19),CNI8(19),CNI9(4 ),
& CNIJ10(6,5),CNI11(5)

REAL*8 TNKL,TNKV,TNK,TNC,PPASL,PPASV,ROLP,ROVP,MULP,MUVP, MU0L,MU1L,
& MU0V,MU1V,DL,DV,TAUL,TAUV,SUML,SUMV,CKLP,CKVP,CK0L ,CK1L,
& CK0V,CK1V
INTEGER I
REAL*8 DV1,DV2,DV3,DV4,DV11,DV21,DV31,DV41

DV1= 0.15541443D+01
DV2= 0.66106305D+02
DV3= 0.55969886D+04
DV4= -0.39259598D+01
DV11= 0.79349503D+00
DV21=-0.13340063D+04
DV31= 0.37884327D+06
DV41= 0.23591474D+01

TNK=TNKL
DL=ROLP/317.763D0
DV=ROVP/317.763D0
TAUL=647.226D0/TNKL
TAUV=647.226D0/TNKV
C VISCOSITY
SUML=0.D0
SUMV=0.D0

DO I=1,4
SUML=SUML+CNI7(I)*TAUL**(I-1)
SUMV=SUMV+CNI7(I)*TAUV**(I-1)
ENDDO
MU0L=1.D0/(DSQRT(TAUL)*SUML)
MU0V=1.D0/(DSQRT(TAUV)*SUMV)

SUML=0.D0
SUMV=0.D0
DO I=1,19
SUML=SUML+CNI8(I)*(DL-1.D0)**CII8(I)*(TAUL-1.D0)**CJI8(I)
SUMV=SUMV+CNI8(I)*(DV-1.D0)**CII8(I)*(TAUV-1.D0)**CJI8(I)
ENDDO
MU1L=DEXP(DL*SUML)
MU1V=DEXP(DV*SUMV)

MULP=55.071D-6*MU0L*MU1L
MUVP=55.071D-6*MU0V*MU1V
C THERMALCONDUCTIVITY
C COMPUTE THE THERMAL CONDUCTIVITY OF LIQUID, VAPOR
IF (TNK.LT.1000.D0)THEN
CKVP=1.0D-04*DEXP(DV1*DLOG(TNK)+DV2/TNK+DV3/TNK**2.D0+DV4) ! W/M.K
ELSE
CKVP=1.0D-04*DEXP(DV11*DLOG(TNK)+DV21/TNK+DV31/TNK**2.D0+DV41) ! W/M.K
ENDIF

IF (TNK.GT.347.15) TNK=347.15
TNC=TNK-273.15D0
CKLP =0.56075D0+1.9947D-03*TNC-7.9003D-06*TNC**2.D0 ! W/M.K
RETURN
END

TABLES.DAT
** DATA FOR THERMODYNAMIC CALCUATIONS OF VAPOR AND LIQUID**
** TABLE 1 FOR CALUCALTIONS OF : LIQUID DENSITY, LIQUID ENTHALPY AND THE DERIVATIVES OF LIQUID DENSITY AND ENTHALPY WITH RESPEC TO P AND T
** TABLE 2 FOR CALUCALTIONS OF BOILING PRESSURE
** TABLE 3-4 FOR CALUCALTIONS OF : VAPOR DENSITY, VAPOR ENTHALPY AND THE DERIVATIVES OF LIQUID DENSITY AND ENTHALPY WITH RESPEC TO P AND T
IN SATURATION REGION (REGION 2)
** TABLE 5 FOR CALUCALTIONS OF : VAPOR DENSITY, VAPOR ENTHALPY AND THE DERIVATIVES OF LIQUID DENSITY AND ENTHALPY WITH RESPEC TO P AND T
IN BOIING REGION (REGION 3)
** TABLE 6 FOR CALUCALTIONS OF SATURATION PRESSURE
** TABLE 7 FOR CALUCALTIONS OF DYNAMIC VISCOSITY OF VAPOR
** TABLE 8 FOR CALUCALTIONS OF DYNAMIC VISCOSITY OF LIQUID
** TABLE 9 FOR CALUCALTIONS OF THERMAL CONDUCTIVITY OF VAPOR
** TABLE 10 FOR CALUCALTIONS OF THERMAL CONDUCTIVITY OF LIQUID

Table1:Coefficients ande xponents of the fundamental equation and itsderivatives
i Ii Ji ni
1 0 -2 0.14632971213167E+00
2 0 -1 -0.84548187169114E+00
3 0 0 -0.37563603672040E+01
4 0 1 0.33855169168385E+01
5 0 2 -0.95791963387872E+00
6 0 3 0.15772038513228E+00
7 0 4 -0.16616417199501E-01
8 0 5 0.81214629983568E-03
9 1 -9 0.28319080123804E-03
10 1 -7 -0.60706301565874E-03
11 1 -1 -0.18990068218419E-01
12 1 0 -0.32529748770505E-01
13 1 1 -0.21841717175414E-01
14 1 3 -0.52838357969930E-04
15 2 -3 -0.47184321073267E-03
16 2 0 -0.30001780793026E-03
17 2 1 0.47661393906987E-04
18 2 3 -0.44141845330846E-05
19 2 17 -0.72694996297594E-15
20 3 -4 -0.31679644845054E-04
21 3 0 -0.28270797985312E-05
22 3 6 -0.85205128120103E-09
23 4 -5 -0.22425281908000E-05
24 4 -2 -0.65171222895601E-06
25 4 10 -0.14341729937924E-12
26 5 -8 -0.40516996860117E-06
27 8 -11 -0.12734301741641E-08
28 8 -6 -0.17424871230634E-09
29 21 -29 -0.68762131295531E-18
30 23 -31 0.14478307828521E-19
31 29 -38 0.26335781662795E-22
32 30 -39 -0.11947622640071E-22
33 31 -40 0.18228094581404E-23
34 32 -41 -0.93537087292458E-25
Table 2.
i ni
1 0.34805185628969E+03
2 -0.11671859879975E+01
3 0.10192970039326E-02
4 0.57254459862746E+03
5 0.13918839778870E+02
Table.3.Coefficientsandexponentsoftheideal-gaspartofthefundamentalequationanditsderivatives
i Ji0 ni0
1 0 -0.96927686500217E+01
2 1 0.10086655968018E+02
3 -5 -0.56087911283020E-02
4 -4 0.71452738081455E-01
5 -3 -0.40710498223928E+00
6 -2 0.14240819171444E+01
7 -1 -0.43839511319450E+01
8 2 -0.28408632460772E+00
9 3 0.21268463753307E-01
Table4.Coefficientsandexponentsoftheresidualpartof thefundamentalequationanditsderivatives
i Ii Ji ni
1. 1. 0. -0.17731742473213E-02
2 1. 1. -0.17834862292358E-01
3 1 2 -0.45996013696365E-01
4 1 3 -0.57581259083432E-01
5 1 6 -0.50325278727930E-01
6 2 1 -0.33032641670203E-04
7 2 2 -0.18948987516315E-03
8 2 4 -0.39392777243355E-02
9 2 7 -0.43797295650573E-01
10 2 36 -0.26674547914087E-04
11 3 0 0.20481737692309E-07
12 3 1 0.43870667284435E-06
13 3 3 -0.32277677238570E-04
14 3 6 -0.15033924542148E-02
15 3 35 -0.40668253562649E-01
16 4 1 -0.78847309559367E-09
17 4 2 0.12790717852285E-07
18 4 3 0.48225372718507E-06
19 5 7 0.22922076337661E-05
20 6 3 -0.16714766451061E-10
21 6 16 -0.21171472321355E-02
22 6 35 -0.23895741934104E+02
23 7 0 -0.59059564324270E-17
24 7 11 -0.12621808899101E-05
25 7 25 -0.38946842435739E-01
26 8 8 0.11256211360459E-10
27 8 36 -0.82311340897998E+01
28 9 13 0.19809712802088E-07
29 10 4 0.10406965210174E-18
30 10 10 -0.10234747095929E-12
31 10 14 -0.10018179379511E-08
32 16 29 -0.80882908646985E-10
33 16 50 0.10693031879409E+00
34 18 57 -0.33662250574171E+00
35 20 20 0.89185845355421E-24
36 20 35 0.30629316876232E-12
37 20 48 -0.42002467698208E-05
38 21 21 -0.59056029685639E-25
39 22 53 0.37826947613457E-05
40 23 39 -0.12768608934681E-14
41 24 26 0.73087610595061E-28
42 24 40 0.55414715350778E-16
43 24 58 -0.94369707241210E-06
Table 5: Coefficients and exponents of the fundamental equation and its derivatives (REGION3)
i Ii Ji ni
1 0 0 0.10658070028513E+01
2 0 0 -0.15732845290239E+02
3 0 1 0.20944396974307E+02
4 0 2 -0.76867707878716E+01
5 0 7 0.26185947787954E+01
6 0 10 -0.28080781148620E+01
7 0 12 0.12053369696517E+01
8 0 23 -0.84566812812502E-02
9 1 2 -0.12654315477714E+01
10 1 6 -0.11524407806681E+01
11 1 15 0.88521043984318E+00
12 1 17 -0.64207765181607E+00
13 2 0 0.38493460186671E+00
14 2 2 -0.85214708824206E+00
15 2 6 0.48972281541877E+01
16 2 7 -0.30502617256965E+01
17 2 22 0.39420536879154E-01
18 2 26 0.12558408424308E+00
19 3 0 -0.27999329698710E+00
20 3 2 0.13899799569460E+01
21 3 4 -0.20189915023570E+01
22 3 16 -0.82147637173963E-02
23 3 26 -0.47596035734923E+00
24 4 0 0.43984074473500E-01
25 4 2 -0.44476435428739E+00
26 4 4 0.90572070719733E+00
27 4 26 0.70522450087967E+00
28 5 1 0.10770512626332E+00
29 5 3 -0.32913623258954E+00
30 5 26 -0.50871062041158E+00
31 6 0 -0.22175400873096E-01
32 6 2 0.94260751665092E-01
33 6 26 0.16436278447961E+00
34 7 2 -0.13503372241348E-01
35 8 26 -0.14834345352472E-01
36 9 2 0.57922953628084E-03
37 9 26 0.32308904703711E-02
38 10 0 0.80964802996215E-04
39 10 1 -0.16557679795037E-03
40 11 26 -0.44923899061815E-04
Table 6: Coefficients of the saturation pressure and temperature equations
i ni
1 0.11670521452767E+04
2 -0.72421316703206E+06
3 -0.17073846940092E+02
4 0.12020824702470E+05
5 -0.32325550322333E+07
6 0.14915108613530E+02
7 -0.48232657361591E+04
8 0.40511340542057E+06
9 -0.23855557567849E+00
10 0.65017534844798E+03
Table 7: Coefficients of the ideal gas part -(Dynamic Viscosity OF VAPOR)
i ni
0 0.100000E+01
1 0.978197
2 0.579829
3 -0.202354
Table 8: Coefficients and exponents of the real fluid part-Dynamic Viscosity
i Ii Ji ni
1 0 0 0.5132047
2 0 1 0.3205656
3 0 4 -0.7782567
4 0 5 0.1885447
5 1 0 0.2151778
6 1 1 0.7317883
7 1 2 0.1241044E+01
8 1 3 0.1476783E+01
9 2 0 -0.2818107
10 2 1 -0.1070786E+01
11 2 2 -0.1263184E+01
12 3 0 0.1778064
13 3 1 0.4605040
14 3 2 0.2340379
15 3 3 -0.4924179
16 4 0 -0.4176610E-01
17 4 3 0.1600435
18 5 1 -0.1578386E-01
19 6 3 -0.3629481E-02
Table 9: Coefficients of the ideal gas part-Thermal Conductivity
i ni
0 0.1000000E+01
1 0.6978267E+01
2 0.2599096E+01
3 -0.9982540
Table 11: Coefficients of the equations pb23
i ni
1 0.34805185629869D3
2 -0.11671859879975D1
3 0.10192970039326D-2
4 0.57254459862746D3
5 0.13918839778870D2
Table 10: Coefficients nij of the first real fluid part-Thermal Conductivity
i: horizontal; j:vertical
0.13293046E+01 0.17018363E+01 0.52246158E+01 0.87127675E+01 -0.18525999E+01
-0.40452437E+00 -0.22156845E+01 -0.10124111E+02 -0.95000611E+01 0.93404690E+00
0.24409490E+00 0.16511057E+01 0.49874687E+01 0.43786606E+01 0.E+00
0.18660751E-01 -0.76736002E+00 -0.27297694E+00 -0.91783782E+00 0.E+00
-0.12961068E+00 0.37283344E+00 -0.43083393E+00 0.E+00 0.E+00
0.44809953E-01 -0.11203160E+00 0.13333849E+00 0.E+00 0.E+00
Table2.31:
i Ii Ji ni
1 0 0 -0.23872489924521D3
2 0 1 0.40421188637945D3
3 0 2 0.11349746881718D3
4 0 6 -0.58457616048039D1
5 0 22 -0.15285482413140D-3
6 0 32 -0.10866707695377D-5
7 1 0 -0.13391744872602D2
8 1 1 0.43211039183559D2
9 1 2 -0.54010067170506D2
10 1 3 0.30535892203916D2
11 1 4 -0.65964749423638D1
12 1 10 0.93965400878363D-2
13 1 32 0.11573647505340D-6
14 2 10 -0.25858641282073D-4
15 2 32 -0.40644363084799D-8
16 3 10 0.66456186191635D-7
17 3 32 0.80670734103027D-10
18 4 32 -0.93477771213947D-12
19 5 32 0.58265442020601D-14
20 6 32 -0.15020185953503D-16

Hope this helps..!
congtuha is offline   Reply With Quote

Reply

Tags
cavitation

Thread Tools Search this Thread
Search this Thread:

Advanced Search
Display Modes

Posting Rules
You may not post new threads
You may not post replies
You may not post attachments
You may not edit your posts

BB code is On
Smilies are On
[IMG] code is On
HTML code is Off
Trackbacks are Off
Pingbacks are On
Refbacks are On


Similar Threads
Thread Thread Starter Forum Replies Last Post
flow past abdominal aorta. Complex BC problem. ziemowitzima OpenFOAM Running, Solving & CFD 1 July 26, 2022 06:12
Axisymmetric Vs 2D Flow problem nikhil FLUENT 0 March 30, 2010 00:52
A problem: reversed flow in ... on outflow. vandadt FLUENT 10 November 10, 2009 17:40
3D Fluid Flow Convergence problem Emily FLUENT 2 March 21, 2007 23:18
transient compressible flow problem (urgent plz) jehanzeb FLUENT 5 August 3, 2004 09:04


All times are GMT -4. The time now is 04:27.