MoDeNa  1.0
Software framework facilitating sequential multi-scale modelling
VLE_main.F90
Go to the documentation of this file.
1 
4 
5 
6 SUBROUTINE vle_mix(rhob,density,chemPot_total,user)
7 
8 
9 !Petsc modules
10  USE petscmanagement
11 
12 
13 !VLE modules
14  USE parameters, ONLY: pi, rgas, kbol, muhs,muhc,mudisp
15  USE basic_variables
16  USE eos_variables, ONLY: fres, eta, eta_start, dhs, mseg, uij, sig_ij, rho, x, z3t
17  USE dft_module
19  USE dft_fcn_module, ONLY: chempot_res
20  IMPLICIT NONE
21 
25 
26 !passed
27  type(userctx) user
28  REAL :: chemPot_total(nc)
29  REAL :: rhob(2,0:nc),density(np)
30 
31 !local
32  REAL, DIMENSION(nc) :: dhs_star
33  REAL :: w(np,nc), lnphi(np,nc)
34  INTEGER :: converg, maxits, its
35 
39 
40  dhs(1:ncomp) = parame(1:ncomp,2) * ( 1.0 - 0.12*exp( -3.0*parame(1:ncomp,3)/t ) ) ! needed for rdf_matrix
41  dhs_star(1:ncomp) = dhs(1:ncomp)/parame(1:ncomp,2)
42 
43  nphas = 2
44  outp = 0 ! output to terminal
45 
46  maxits = 800
47  its = 0
48 
49  converg = 0
50 
51  Do while(converg == 0)
52 
53  CALL start_var (converg,user) ! gets starting values, sets "val_init"
54  If(converg == 1) exit
55  If(its > maxits) exit
56 
57  !increase pressure until VLE is found
58  p = 1.01 * p
59  its = its + 1
60  End Do
61 
62  If(its > maxits) stop 'SurfaceTension tool: no vapor-liquid equilibrium could be found.'
63 
64 
65 
66 ! rhob(phase,0): molecular density
67  rhob(1,0) = dense(1) / ( pi/6.0* sum( xi(1,1:ncomp) * parame(1:ncomp,1) * dhs(1:ncomp)**3 ) )
68  rhob(2,0) = dense(2) / ( pi/6.0* sum( xi(2,1:ncomp) * parame(1:ncomp,1) * dhs(1:ncomp)**3 ) )
69  ! rhob(phase,i): molecular component density (with i=(1,...ncomp) ) in units (1/A^3)
70  rhob(1,1:ncomp) = rhob(1,0)*xi(1,1:ncomp)
71  rhob(2,1:ncomp) = rhob(2,0)*xi(2,1:ncomp)
72 
73 ! --- get density in SI-units (kg/m**3) -------------------------------
74  CALL si_dens ( density, w )
75 
76 !--- calculate residual chemical potentials
77  ensemble_flag = 'tv' ! this flag is for: mu_res=mu_res(T,rho)
78  densta(1) = dense(1) ! Index 1 is for liquid density (here: packing fraction eta)
79  densta(2) = dense(2) ! Index 2 is for vapour density (here: packing fraction eta)
80  CALL fugacity (lnphi)
81  chempot_res(1:ncomp) = lnphi(1,1:ncomp)
82  chempot_total(1:ncomp) = lnphi(1,1:ncomp) + log( rhob(1,1:ncomp) ) ! my0 = mu_res(T,rho_bulk_L) + ln(rho_bulk_l)
83 
84 
88 
89 
90 IF(user%rank == 0) THEN
91  WRITE(*,*) '--------------------------------------------------'
92  WRITE(*,*)'RESULT OF PHASE EQUILIBRIUM CALCULATION'
93  WRITE (*,*) ' '
94  WRITE (*,*) 'temperature ',t, 'K, and p=', p/1.e5,' bar'
95  WRITE (*,*) 'x1_liquid ',xi(1,1),' x1_vapor', xi(2,1)
96  WRITE (*,*) 'densities ',rhob(1,0), rhob(2,0)
97  WRITE (*,*) 'dense ',dense(1), dense(2)
98  WRITE (*,*) 'density [kg/m3] ',density(1), density(2)
99  write (*,*) 'chemical potentials comp1' , lnphi(1,1) + log( rhob(1,1) ), lnphi(2,1) + lnx(2,1) + log(rhob(2,0)) !LOG( rhob(2,1) )
100  write (*,*) 'chemical potentials comp2' ,lnphi(1,2) + log( rhob(1,2) ), lnphi(2,2) + log( rhob(2,2) )
101 END IF
102 
103 
104 
105 
106 END SUBROUTINE vle_mix
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains constant...
Definition: modules.f90:6
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW Module DFT_MODULE This module...
Definition: modules.f90:272
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains paramete...
Definition: modules.f90:120
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains the vari...
Definition: modules.f90:327
subroutine vle_mix(rhob, density, chemPot_total, user)
Definition: VLE_main.F90:7
In this module, the application context is defined.
Definition: mod_PETSc.F90:7
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains paramete...
Definition: modules.f90:29
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains paramete...
Definition: modules.f90:220