MoDeNa  1.0
Software framework facilitating sequential multi-scale modelling
phys_prop.f90
Go to the documentation of this file.
1 
8 module phys_prop
9  use constants, only: dp
10  implicit none
11  private
12  integer :: rb_kx=4,rb_iknot=0,rb_inbvx,rb_nx
13  real(dp), dimension(:), allocatable :: rb_tx,rb_coef
14  integer :: por_kx=2,por_iknot=0,por_inbvx,por_nx
15  real(dp), dimension(:), allocatable :: por_tx,por_coef
16  integer :: visc_kx=2,visc_iknot=0,visc_inbvx,visc_nx
17  real(dp), dimension(:), allocatable :: visc_tx,visc_coef
18  public volume_balance,dispress,min_film_thickness,rb_spline_ini,&
19  rb,rb_der,porosity_spline_ini,porosity,visc_spline_ini,visc
20 contains
21 !********************************BEGINNING*************************************
23 pure subroutine volume_balance(y,vt,fs)
24  use globals
25  real(dp), intent(out) :: fs
26  real(dp), intent(out) :: vt
27  real(dp), dimension(:), intent(in) :: y
28  integer :: i,neq
29  real(dp) :: vf,vs
30  neq=size(y)
31  vf=0
32  vs=0
33  do i=1,neq
34  if (y(i)<strutfilmparameter*y(1)) then
35  vf=vf+2*pi*dr*(0.5_dp+i-1)*y(i)*dr
36  else
37  vs=vs+2*pi*dr*(0.5_dp+i-1)*y(i)*dr
38  endif
39  enddo
40  vs=vs+pi*y(neq)/3*(rd**2+rc*rd+rc**2)-pi*y(neq)*rd**2
41  vt=vf+vs
42  fs=vs/vt
43 end subroutine volume_balance
44 !***********************************END****************************************
45 
46 
47 !********************************BEGINNING*************************************
49 pure subroutine dispress(h,dispr,dph)
50  use globals
51  real(dp), intent(in) :: h
52  real(dp), intent(out) :: dispr
53  real(dp), intent(out) :: dph
54  dispr=bdp*((hdp/h)**(ndp-1)-(hdp/h)**(mdp-1))*(hdp-cdp)
55  dph=(bdp*(hdp/h)**mdp*(hdp*mdp+cdp*(h-h*mdp))-&
56  bdp*(hdp/h)**ndp*(hdp*ndp+cdp*(h-h*ndp)))/(h*hdp)
57 end subroutine dispress
58 !***********************************END****************************************
59 
60 
61 !********************************BEGINNING*************************************
63 subroutine min_film_thickness(y,hmin,hloc,havg)
64  use globals
65  real(dp), dimension(:), intent(in) :: y
66  real(dp), intent(out) :: hmin
67  real(dp), intent(out) :: hloc
68  real(dp), intent(out) :: havg
69  integer :: i,n
70  hmin=minval(y,dim=1)
71  hloc=minloc(y,dim=1)*dr
72  havg=0
73  n=size(y,1)
74  do i=1,n
75  if (y(i)<strutfilmparameter*y(1)) then
76  havg=havg+2*pi*dr*(0.5_dp+i-1)*y(i)*dr
77  else
78  exit
79  endif
80  enddo
81  havg=havg/(pi*(dr*(0.5_dp+i-2))**2)
82 end subroutine min_film_thickness
83 !***********************************END****************************************
84 
85 
86 !********************************BEGINNING*************************************
88 real(dp) function rb_der(t)
89  use bspline_module
90  real(dp), intent(in) :: t
91  integer :: idx,iflag
92  idx=1
93  call db1val(t,idx,rb_tx,rb_nx,rb_kx,rb_coef,rb_der,iflag,rb_inbvx)
94  if (iflag /= 0) then
95  print*, 'evaluation of bubble radius derivative from spline failed',&
96  iflag
97  stop
98  endif
99 endfunction rb_der
100 !***********************************END****************************************
101 
102 
103 !********************************BEGINNING*************************************
105 real(dp) function rb(t)
106  use bspline_module
107  real(dp), intent(in) :: t
108  integer :: idx,iflag
109  idx=0
110  call db1val(t,idx,rb_tx,rb_nx,rb_kx,rb_coef,rb,iflag,rb_inbvx)
111  if (iflag /= 0) then
112  print*, 'evaluation of bubble radius from spline failed',iflag
113  stop
114  endif
115 endfunction rb
116 !***********************************END****************************************
117 
118 
119 !********************************BEGINNING*************************************
121 subroutine rb_spline_ini(bblgr_res)
122  use bspline_module
124  real(dp), dimension(:,:), intent(in) :: bblgr_res
125  integer :: iflag
126  rb_nx=size(bblgr_res(:,1))
127  if (allocated(rb_tx)) deallocate(rb_tx)
128  if (allocated(rb_coef)) deallocate(rb_coef)
129  allocate(rb_tx(rb_nx+rb_kx),rb_coef(rb_nx))
130  rb_tx=0
131  call db1ink(bblgr_res(:,1),rb_nx,bblgr_res(:,2),&
132  rb_kx,rb_iknot,rb_tx,rb_coef,iflag)
133  rb_inbvx=1
134  if (iflag /= 0) then
135  print*, 'initialization of bubble radius spline failed'
136  stop
137  endif
138 end subroutine rb_spline_ini
139 !***********************************END****************************************
140 
141 
142 !********************************BEGINNING*************************************
144 real(dp) function porosity(t)
145  use bspline_module
146  real(dp), intent(in) :: t
147  integer :: idx,iflag
148  idx=0
149  call db1val(t,idx,por_tx,por_nx,por_kx,por_coef,porosity,iflag,por_inbvx)
150  if (iflag /= 0) then
151  print*, 'evaluation of porosity from spline failed',iflag
152  stop
153  endif
154 endfunction porosity
155 !***********************************END****************************************
156 
157 
158 !********************************BEGINNING*************************************
160 subroutine porosity_spline_ini(bblgr_res)
161  use bspline_module
163  real(dp), dimension(:,:), intent(in) :: bblgr_res
164  integer :: iflag
165  por_nx=size(bblgr_res(:,1))
166  if (allocated(por_tx)) deallocate(por_tx)
167  if (allocated(por_coef)) deallocate(por_coef)
168  allocate(por_tx(por_nx+por_kx),por_coef(por_nx))
169  por_tx=0
170  call db1ink(bblgr_res(:,1),por_nx,bblgr_res(:,3),&
171  por_kx,por_iknot,por_tx,por_coef,iflag)
172  por_inbvx=1
173  if (iflag /= 0) then
174  print*, 'initialization of porosity spline failed'
175  stop
176  endif
177 end subroutine porosity_spline_ini
178 !***********************************END****************************************
179 
180 
181 !********************************BEGINNING*************************************
183 real(dp) function visc(t)
184  use bspline_module
185  real(dp), intent(in) :: t
186  integer :: idx,iflag
187  idx=0
188  call db1val(t,idx,visc_tx,visc_nx,visc_kx,visc_coef,visc,iflag,visc_inbvx)
189  if (iflag /= 0) then
190  print*, 'evaluation of viscosity from spline failed',iflag
191  stop
192  endif
193 endfunction visc
194 !***********************************END****************************************
195 
196 
197 !********************************BEGINNING*************************************
199 subroutine visc_spline_ini(bblgr_res)
200  use bspline_module
202  real(dp), dimension(:,:), intent(in) :: bblgr_res
203  integer :: iflag
204  visc_nx=size(bblgr_res(:,1))
205  if (allocated(visc_tx)) deallocate(visc_tx)
206  if (allocated(visc_coef)) deallocate(visc_coef)
207  allocate(visc_tx(visc_nx+visc_kx),visc_coef(visc_nx))
208  visc_tx=0
209  call db1ink(bblgr_res(:,1),visc_nx,bblgr_res(:,4),&
210  visc_kx,visc_iknot,visc_tx,visc_coef,iflag)
211  visc_inbvx=1
212  if (iflag /= 0) then
213  print*, 'initialization of viscosity spline failed'
214  stop
215  endif
216 end subroutine visc_spline_ini
217 !***********************************END****************************************
218 end module phys_prop
double porosity(int ***amat)
Calculates porosity.
Definition: geometry.cc:70
real(dp) strutfilmparameter
parameter determining strut-film boundary
Definition: globals.f90:18
real(dp) rc
total window size (radius)
Definition: globals.f90:18
real(dp) cdp
disjoining pressure constant
Definition: globals.f90:18
real(dp) bdp
disjoining pressure constant, set to zero for no DP
Definition: globals.f90:18
real(dp) ndp
disjoining pressure constant
Definition: globals.f90:18
namespace with global variables
Definition: globals.f90:8
real(dp) rd
computational domain size (radius)
Definition: globals.f90:18
real(dp) hdp
disjoining pressure constant
Definition: globals.f90:18
real(dp) mdp
disjoining pressure constant
Definition: globals.f90:18
real(dp) dr
mesh points spacing
Definition: globals.f90:18