CubicEoS Derived Type

type, public, extends(ArModel) :: CubicEoS

Cubic Equation of State.

Generic Cubic Equation of State as defined by Michelsen and Mollerup with a parameter that is not constant, and a parameter that depends on it. In the case of a two parameter EoS like PengRobinson the is the same for all components so it can be considered as a constant instead of a variable. The expression of the Equation is:


Components

Type Visibility Attributes Name Initial
real(kind=pr), public, allocatable :: ac(:)

Attractive critical parameter

class(AlphaFunction), public, allocatable :: alpha

AlphaFunction derived type.

Uses the abstract derived type AlphaFunction to define the Alpha function that the CubicEoS will use. The Alpha function receives the reduced temperature and returns the values of alpha and its derivatives, named a, dadt and dadt2 respectively.

Examples

Callign the AlphaFunction of a setted up model.

use yaeos, only: CubicEoS, PengRobinson76

type(CubicEoS) :: eos
eos = PengRobinson76(tc, pc, w)
call eos%alpha%alpha(Tr, a, dadt, dadt2)
real(kind=pr), public, allocatable :: b(:)

Repulsive parameter

type(Substances), public :: components

Substances contained in the module

real(kind=pr), public, allocatable :: del1(:)

paramter

real(kind=pr), public, allocatable :: del2(:)

paramter

class(CubicMixRule), public, allocatable :: mixrule

CubicMixRule derived type.

Uses the abstract derived type CubicMixRule to define the mixing rule that the CubicEoS will use. It includes internally three methods to calculate the corresponding parameters for the Cubic EoS: Dmix, Bmix and D1mix.

Examples

Calculation of the B parameter.

use yaeos, only: CubicEoS, PengRobinson76
type(CubicEoS) :: eos
eos = PengRobinson76(tc, pc, w)
call eos%mixrule%Bmix(n, eos%b, B, dBi, dBij)

Calculation of the D parameter.

use yaeos, only: CubicEoS, PengRobinson76
type(CubicEoS) :: eos
eos = PengRobinson76(tc, pc, w)

! The mixing rule takes the `a` parameters of the components so
! they should be calculated externally
call eos%alpha%alpha(Tr, a, dadt, dadt2)
a = a * eos%ac
dadt = dadt * eos%ac / eos%components%Tc
dadt = dadt * eos%ac / eos%components%Tc**2
! Calculate parameter
call eos%mixrule%Dmix(n, T, a, dadt, dadt2, D, dDdT, dDdT2, dDi, dDidT, dDij)

Calculation of the D1 parameter.

use yaeos, only: CubicEoS, PengRobinson76
type(CubicEoS) :: eos
eos = PengRobinson76(tc, pc, w)
call eos%mixrule%D1mix(n, eos%del1, D1, dD1i, dD1ij)
character(len=:), public, allocatable :: name

Name of the model


Type-Bound Procedures

procedure, public :: Cp_residual_vt

  • private subroutine Cp_residual_vt(eos, n, V, T, Cp)

    Calculate residual heat capacity pressure constant given V and T.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out) :: Cp

    heat capacity P constant [bar L / K]

procedure, public :: Cv_residual_vt

  • private subroutine Cv_residual_vt(eos, n, V, T, Cv)

    Calculate residual heat capacity volume constant given V and T.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out) :: Cv

    heat capacity V constant [bar L / K]

procedure, public :: Psat_pure

  • private function Psat_pure(eos, ncomp, T)

    Calculation of saturation pressure of a pure component using the secant method.

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model that will be used

    integer, intent(in) :: ncomp

    Number of component in the mixture from which the saturation pressure will be calculated

    real(kind=pr), intent(in) :: T

    Temperature [K]

    Return Value real(kind=pr)

procedure, public :: enthalpy_residual_vt

  • private subroutine enthalpy_residual_vt(eos, n, V, T, Hr, HrV, HrT, Hrn)

    Calculate residual enthalpy given volume and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: Hr

    Residual enthalpy [bar L]

    real(kind=pr), intent(out), optional :: HrV

    real(kind=pr), intent(out), optional :: HrT

    real(kind=pr), intent(out), optional :: Hrn(size(n))

procedure, public :: entropy_residual_vt

  • private subroutine entropy_residual_vt(eos, n, V, T, Sr, SrV, SrT, Srn)

    Calculate residual entropy given volume and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: Sr

    Entropy [bar L / K]

    real(kind=pr), intent(out), optional :: SrV

    real(kind=pr), intent(out), optional :: SrT

    real(kind=pr), intent(out), optional :: Srn(size(n))

procedure, public :: get_v0 => v0

  • public function v0(self, n, p, t)

    Cubic EoS volume initializer. For a Cubic Equation of State, the covolume calculated with the mixing rule is a good estimate for the initial volume solver on the liquid region.

    Arguments

    Type IntentOptional Attributes Name
    class(CubicEoS), intent(in) :: self
    real(kind=pr), intent(in) :: n(:)
    real(kind=pr), intent(in) :: p
    real(kind=pr), intent(in) :: t

    Return Value real(kind=pr)

procedure, public :: gibbs_residual_vt

  • private subroutine gibbs_residual_vt(eos, n, V, T, Gr, GrV, GrT, Grn)

    Calculate residual Gibbs energy given volume and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: Gr

    Gibbs energy [bar L]

    real(kind=pr), intent(out), optional :: GrV

    real(kind=pr), intent(out), optional :: GrT

    real(kind=pr), intent(out), optional :: Grn(size(n))

procedure, public :: internal_energy_residual_vt

  • private subroutine internal_energy_residual_vt(eos, n, V, T, Ur, UrV, UrT, Urn)

    Calculate residual internal energy given volume and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: Ur

    Internal energy [bar L]

    real(kind=pr), intent(out), optional :: UrV

    real(kind=pr), intent(out), optional :: UrT

    real(kind=pr), intent(out), optional :: Urn(size(n))

procedure, public :: lnfug_vt

  • private subroutine lnfug_vt(eos, n, V, T, P, lnf, dlnfdV, dlnfdT, dlnfdn, dPdV, dPdT, dPdn)

    Calculate natural logarithm of fugacity given volume and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Mixture mole numbers

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: P

    Pressure [bar]

    real(kind=pr), intent(out), optional :: lnf(size(n))

    vector

    real(kind=pr), intent(out), optional :: dlnfdV(size(n))

    Volume derivative

    real(kind=pr), intent(out), optional :: dlnfdT(size(n))

    Temp derivative

    real(kind=pr), intent(out), optional :: dlnfdn(size(n),size(n))

    compositional derivative

    real(kind=pr), intent(out), optional :: dPdV

    real(kind=pr), intent(out), optional :: dPdT

    real(kind=pr), intent(out), optional :: dPdn(:)

procedure, public :: lnphi_pt

  • private subroutine lnphi_pt(eos, n, P, T, V, root_type, lnPhi, dlnPhidP, dlnPhidT, dlnPhidn, dPdV, dPdT, dPdn)

    Calculate natural logarithm of fugacity given pressure and temperature.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Mixture mole numbers

    real(kind=pr), intent(in) :: P

    Pressure [bar]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: V

    Volume [L]

    character(len=*), intent(in) :: root_type

    Type of root desired [“liquid”, “vapor”, “stable”]

    real(kind=pr), intent(out), optional :: lnPhi(size(n))

    vector

    real(kind=pr), intent(out), optional :: dlnPhidP(size(n))

    ln(phi) Presssure derivative

    real(kind=pr), intent(out), optional :: dlnPhidT(size(n))

    ln(phi) Temperature derivative

    real(kind=pr), intent(out), optional :: dlnPhidn(size(n),size(n))

    ln(phi) compositional derivative

    real(kind=pr), intent(out), optional :: dPdV

    real(kind=pr), intent(out), optional :: dPdT

    real(kind=pr), intent(out), optional :: dPdn(size(n))

procedure, public :: lnphi_vt

  • private subroutine lnphi_vt(eos, n, V, T, P, lnPhi, dlnPhidP, dlnPhidT, dlnPhidn, dPdV, dPdT, dPdn)

    Calculate natural logarithm of fugacity coefficent.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Mixture mole numbers

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out), optional :: P

    Pressure [bar]

    real(kind=pr), intent(out), optional :: lnPhi(size(n))

    vector

    real(kind=pr), intent(out), optional :: dlnPhidP(size(n))

    Presssure derivative

    real(kind=pr), intent(out), optional :: dlnPhidT(size(n))

    Temp derivative

    real(kind=pr), intent(out), optional :: dlnPhidn(size(n),size(n))

    compositional derivative

    real(kind=pr), intent(out), optional :: dPdV

    real(kind=pr), intent(out), optional :: dPdT

    real(kind=pr), intent(out), optional :: dPdn(:)

procedure, public :: pressure

  • private subroutine pressure(eos, n, V, T, P, dPdV, dPdT, dPdn)

    Calculate pressure.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(ArModel), intent(in) :: eos

    Model

    real(kind=pr), intent(in) :: n(:)

    Moles number vector

    real(kind=pr), intent(in) :: V

    Volume [L]

    real(kind=pr), intent(in) :: T

    Temperature [K]

    real(kind=pr), intent(out) :: P

    Pressure [bar]

    real(kind=pr), intent(out), optional :: dPdV

    real(kind=pr), intent(out), optional :: dPdT

    real(kind=pr), intent(out), optional :: dPdn(:)

procedure, public :: residual_helmholtz => GenericCubic_Ar

  • public subroutine GenericCubic_Ar(self, n, v, t, ar, arv, ArT, artv, arv2, ArT2, Arn, ArVn, ArTn, Arn2)

    Residual Helmholtz Energy for a generic Cubic Equation of State.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(CubicEoS), intent(in) :: self
    real(kind=pr), intent(in) :: n(:)

    Number of moles

    real(kind=pr), intent(in) :: v

    Volume [L]

    real(kind=pr), intent(in) :: t

    Temperature [K]

    real(kind=pr), intent(out), optional :: ar

    Residual Helmholtz

    real(kind=pr), intent(out), optional :: arv

    real(kind=pr), intent(out), optional :: ArT

    real(kind=pr), intent(out), optional :: artv

    real(kind=pr), intent(out), optional :: arv2

    real(kind=pr), intent(out), optional :: ArT2

    real(kind=pr), intent(out), optional :: Arn(size(n))

    real(kind=pr), intent(out), optional :: ArVn(size(n))

    real(kind=pr), intent(out), optional :: ArTn(size(n))

    real(kind=pr), intent(out), optional :: Arn2(size(n),size(n))

procedure, public :: set_delta1

  • public subroutine set_delta1(self, delta1)

    Arguments

    Type IntentOptional Attributes Name
    class(CubicEoS) :: self
    real(kind=pr), intent(in) :: delta1(:)

procedure, public :: set_mixrule

  • public subroutine set_mixrule(self, mixrule)

    Arguments

    Type IntentOptional Attributes Name
    class(CubicEoS), intent(inout) :: self
    class(CubicMixRule), intent(in) :: mixrule

procedure, public :: volume

  • public subroutine volume(eos, n, P, T, V, root_type)

    Volume solver optimized for Cubic Equations of State.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(CubicEoS), intent(in) :: eos
    real(kind=pr), intent(in) :: n(:)
    real(kind=pr), intent(in) :: P
    real(kind=pr), intent(in) :: T
    real(kind=pr), intent(out) :: V
    character(len=*), intent(in) :: root_type