MoDeNa  1.0
Software framework facilitating sequential multi-scale modelling
VLE_main.f90
1 
3 
4 
5 SUBROUTINE vle_mix(rhob,density,chemPot_total,compID)
6 
7  USE parameters, ONLY: pi, rgas, kbol
9  USE eos_variables, ONLY: fres, eta, eta_start, dhs, mseg, uij, sig_ij, rho, x, z3t
10  USE dft_module
12  IMPLICIT NONE
13 
14 
18 
19 
20 !passed
21  REAL :: chempot_total(nc)
22  REAL :: rhob(2,0:nc),density(np)
23  INTEGER :: compid
24 
25 !local
26  REAL, DIMENSION(nc) :: dhs_star
27  REAL :: w(np,nc), lnphi(np,nc)
28  INTEGER :: converg
29  CHARACTER(LEN=4) :: char_ncomp
30  REAL :: polymer_density
31  INTEGER :: i, maxits, its
32  CHARACTER (LEN=50) :: filename
33 
34 
38 
39  dhs(1:ncomp) = parame(1:ncomp,2) * ( 1.0 - 0.12*exp( -3.0*parame(1:ncomp,3)/t ) ) ! needed for rdf_matrix
40  dhs_star(1:ncomp) = dhs(1:ncomp)/parame(1:ncomp,2)
41 
42  nphas = 2
43  outp = 0 ! output to terminal
44  converg = 0
45  maxits = 800
46  its = 0
47 
48  Do while(converg == 0)
49 
50  CALL start_var (converg) ! gets starting values, sets "val_init"
51  If(converg == 1) exit
52  If(its > maxits) exit
53 
54  !increase pressure until VLE is found
55  p = 1.01 * p
56  its = its + 1
57  End Do
58 
59  If(its > maxits) stop 'Polymer_density tool: no liquid density could be found.'
60 
61  ! rhob(phase,0): molecular density
62  rhob(1,0) = dense(1) / ( pi/6.0* sum( xi(1,1:ncomp) * parame(1:ncomp,1) * dhs(1:ncomp)**3 ) )
63  rhob(2,0) = dense(2) / ( pi/6.0* sum( xi(2,1:ncomp) * parame(1:ncomp,1) * dhs(1:ncomp)**3 ) )
64  ! rhob(phase,i): molecular component density (with i=(1,...ncomp) ) in units (1/A^3)
65  rhob(1,1:ncomp) = rhob(1,0)*xi(1,1:ncomp)
66  rhob(2,1:ncomp) = rhob(2,0)*xi(2,1:ncomp)
67 
68  ! get density in SI-units (kg/m**3)
69  CALL si_dens ( density, w )
70 
71  ! calculate residual chemical potentials
72  ensemble_flag = 'tv' ! this flag is for: mu_res=mu_res(T,rho)
73  densta(1) = dense(1) ! Index 1 is for liquid density (here: packing fraction eta)
74  densta(2) = dense(2) ! Index 2 is for vapour density (here: packing fraction eta)
75  CALL fugacity (lnphi)
76  chempot_total(1:ncomp) = lnphi(1,1:ncomp)! + LOG( rhob(1,1:ncomp) ) ! my0 = mu_res(T,rho_bulk_L) + ln(rho_bulk_l)
77 
78 ! WRITE(*,*) '--------------------------------------------------'
79 ! WRITE(*,*)'RESULT OF PHASE EQUILIBRIUM CALCULATION'
80 ! WRITE (char_ncomp,'(I3)') ncomp
81 ! WRITE (*,*) 'T = ',t, 'K, and p =', p/1.E5,' bar'
82 ! WRITE(*,*)' '
83 ! WRITE(*,'(t15,4(a12,1x),10x,a)') (compna(i),i=1,ncomp)
84 !
85 ! write(*,*)'Mass fraction:'
86 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE I w', (w(1,i),i=1,ncomp)
87 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE II w', (w(2,i),i=1,ncomp)
88 !
89 ! write(*,*)'Molar composition:'
90 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE I x', (EXP(lnx(1,i)),i=1,ncomp)
91 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE II x', (EXP(lnx(2,i)),i=1,ncomp)
92 ! WRITE(*,*)' '
93 ! !!WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE I density', (rhob(1,i),i=1,ncomp)
94 ! !! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE II density', (rhob(2,i),i=1,ncomp)
95 ! !!WRITE(*,*)' '
96 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE I chemPot', (lnphi(1,i) + LOG(rhob(1,i)),i=1,ncomp)
97 ! WRITE(*,'(2x,a,'//char_ncomp//'(g13.6,1x))') 'PHASE II chemPot', (lnphi(2,i) + LOG(rhob(2,i)),i=1,ncomp)
98 ! WRITE(*,*)' '
99 ! !!WRITE(*,*)'Phase densities '
100 ! WRITE(*,'(2x,a,2(g13.6,1x))') 'SI-DENSITY [kg/m3] ', density(1),density(2)
101 ! !!WRITE(*,'(2x,a,2(g13.6,1x))') 'NUMBER-DENSITY ', rhob(1,0),rhob(2,0)
102 !
103 ! WRITE(*,*)
104 
105 
106  write(*,*)' '
107  write(*,*)'--------------------------------------------'
108  write(*,*)'Output detailed model:'
109  !write(*,*)'T /K:',t,'p/bar:',p/1.E5
110  write(*,*)'Liquid density /kg/m3:', max(density(1),density(2))
111  write(*,*)'--------------------------------------------'
112  write(*,*)' '
113 
114 
115 
117 
118  polymer_density = max(density(1),density(2)) !* w(1,1)
119 
120  filename='./out.txt'
121  CALL file_open(filename,78)
122  write(78,*) polymer_density
123  !write(*,*)'Polymer_density [kg/m3]:',Polymer_density
124 
125 
126 
127 
128 
129 ! WRITE (*,*) ' '
130 ! WRITE (*,*) 'temperature ',t, 'K, and p=', p/1.E5,' bar'
131 ! WRITE (*,*) 'x1_liquid ',xi(1,1),' x1_vapor', xi(2,1)
132 ! WRITE (*,*) 'densities ',rhob(1,0), rhob(2,0)
133 ! WRITE (*,*) 'dense ',dense(1), dense(2)
134 ! WRITE (*,*) 'density [kg/m3] ',density(1), density(2)
135 ! write (*,*) 'chemical potentials comp1' , lnphi(1,1) + LOG( rhob(1,1) ), lnphi(2,1) + LOG( rhob(2,1) )
136 ! write (*,*) 'chemical potentials comp2' ,lnphi(1,2) + LOG( rhob(1,2) ), lnphi(2,2) + LOG( rhob(2,2) )
137 !
138 
139 
140 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
subroutine vle_mix(rhob, density, chemPot_total, user)
Definition: VLE_main.F90:7
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains paramete...
Definition: modules.f90:29
WWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWWW This module contains paramete...
Definition: modules.f90:220