MoDeNa  1.0
Software framework facilitating sequential multi-scale modelling
model.f90
Go to the documentation of this file.
1 
7 module model
8  use constants, only: dp
9  implicit none
10  private
11  real(dp), parameter :: &
12  s=1/sqrt(3._dp)
13  real(dp) :: q
15  real(dp), dimension(:,:), allocatable :: bblgr_res
16  public odesystem,set_initial_conditions,update_domain_size,q
17 contains
18 !********************************BEGINNING*************************************
23 subroutine odesystem(neq, t, y, ydot)
24  use constants, only: pi
25  use globals
26  use phys_prop, only: dispress,rb,visc
27  integer, intent(in) :: neq
28  real(dp), intent(in) :: t
29  real(dp), intent(in) :: y(neq)
30  real(dp), intent(out) :: ydot(neq)
31  integer :: i
32  real(dp) :: z,ze,zw,zee,zww
33  real(dp) :: lame,lamw
34  real(dp) :: h,he,hw,hee,hww,heee,hwww
35  real(dp) :: he1,hw1,he2,hw2,he3,hw3
36  real(dp) :: fluxe,fluxw
37  real(dp) :: vf,vs,vt
38  real(dp) :: dispr,dph
39  if (viscositymodel=="fromFile") then
40  mu=visc(t)
41  endif
42  call update_domain_size(t,y)
43  do i=1,neq
44  if (i==1) then
45  z=dr/2
46  ze=dr
47  zee=3*dr/2
48  lame=(ze-z)/(zee-z)
49  h=y(i)
50  hee=y(i+1)
51  hw=h
52  he=hee*lame+h*(1-lame)
53  heee=y(i+2)*lame+hee*(1-lame)
54  he1=(hee-h)/(dr)
55  he2=(hee-2*he+h)/(dr**2/4)
56  he3=(heee-2*hee+2*h-hw)/(dr**3/4)
57  fluxw=0
58  call dispress(he,dispr,dph)
59  fluxe=gam*he**3*(2*he1**3/ze+he1**5/ze+he1*(1+3*ze**2*he2**2)/ze-&
60  he2-ze*he3-he1**2*(he2+ze*he3))/(1+he1**2)**2.5_dp+&
61  dph*he1*he**3*ze
62  elseif (i==neq) then
63  zww=z
64  zw=ze
65  z=zee
66  lamw=(zw-zww)/(z-zww)
67  hww=y(i-1)
68  h=y(i)
69  hw=h*lamw+hww*(1-lamw)
70  he=h+dr*s/2
71  hwww=hww*lamw+y(i-2)*(1-lamw)
72  hw1=(h-hww)/(dr)
73  hw2=(h-2*hw+hww)/(dr**2/4)
74  hw3=(he-2*h+2*hww-hwww)/(dr**3/4)
75  call dispress(he,dispr,dph)
76  fluxw=gam*hw**3*(2*hw1**3/zw+hw1**5/zw+hw1*(1+3*zw**2*hw2**2)/zw-&
77  hw2-zw*hw3-hw1**2*(hw2+zw*hw3))/(1+hw1**2)**2.5_dp+&
78  dph*hw1*hw**3*zw
79  fluxe=-q*3*mu/2/pi
80  else
81  zww=z
82  zw=ze
83  z=zee
84  ze=ze+dr
85  zee=ze+dr/2
86  lamw=(zw-zww)/(z-zww)
87  lame=(ze-z)/(zee-z)
88  hww=y(i-1)
89  h=y(i)
90  hee=y(i+1)
91  hw=h*lamw+hww*(1-lamw)
92  he=hee*lame+h*(1-lame)
93  if (i==2) then
94  hwww=hww
95  else
96  hwww=hww*lamw+y(i-2)*(1-lamw)
97  endif
98  if (i==neq-1) then
99  heee=hee+dr*s/2
100  else
101  heee=y(i+2)*lame+hee*(1-lame)
102  endif
103  hw1=(h-hww)/(dr)
104  hw2=(h-2*hw+hww)/(dr**2/4)
105  hw3=(he-2*h+2*hww-hwww)/(dr**3/4)
106  he1=(hee-h)/(dr)
107  he2=(hee-2*he+h)/(dr**2/4)
108  he3=(heee-2*hee+2*h-hw)/(dr**3/4)
109  call dispress(he,dispr,dph)
110  fluxw=gam*hw**3*(2*hw1**3/zw+hw1**5/zw+hw1*(1+3*zw**2*hw2**2)/zw-&
111  hw2-zw*hw3-hw1**2*(hw2+zw*hw3))/(1+hw1**2)**2.5_dp+&
112  dph*hw1*hw**3*zw
113  call dispress(he,dispr,dph)
114  fluxe=gam*he**3*(2*he1**3/ze+he1**5/ze+he1*(1+3*ze**2*he2**2)/ze-&
115  he2-ze*he3-he1**2*(he2+ze*he3))/(1+he1**2)**2.5_dp+&
116  dph*he1*he**3*ze
117  endif
118  ydot(i)=(fluxe-fluxw)/(z*dr)/3/mu
119  enddo
120 end subroutine odesystem
121 !***********************************END****************************************
122 
123 
124 !********************************BEGINNING*************************************
126 subroutine set_initial_conditions(y)
128  use in_out, only: load_bubble_growth
129  use phys_prop, only: rb_spline_ini,visc_spline_ini,porosity_spline_ini
130  real(dp), dimension(:), intent(out) :: y
131  integer :: i,neq,cp_por_ind
132  real(dp) :: rs,ri,cp_por
133  neq=size(y)
134  if (growthratemodel=="fromFile" .or. viscositymodel=="fromFile") then
135  call load_bubble_growth(bblgr_res)
136  endif
137  if (growthratemodel=="constantGrowth") then
138  dr=rd/neq
139  rs=rd*sqrt((1+s**2)/s**2)*dstr
140  y=hi
141  do i=1,neq
142  ri=dr*(0.5_dp+i-1)
143  if (i>neq*(1-dstr)) then
144  y(i)=(rs+hi)-sqrt(rs**2-(ri-(1-dstr)*rd)**2)
145  endif
146  ! y(i)=s/Rd/2*r(i)**2+hi
147  ! y(i)=s/Rd**2/3*r(i)**3+hi
148  enddo
149  rc0=rd+y(neq)/sqrt(3.0_dp)
150  rc=rc0
151  elseif (growthratemodel=="fromFile") then
152  call rb_spline_ini(bblgr_res)
153  call porosity_spline_ini(bblgr_res)
154  !TODO find starting point more more precisely
155  cp_por_ind=minloc(abs(bblgr_res(:,3)-0.70_dp),dim=1)
156  rs=bblgr_res(cp_por_ind,2)
157  initialtime=bblgr_res(cp_por_ind,1)
158  its=(bblgr_res(size(bblgr_res(:,1), dim=1),1)-initialtime)/timestep-1
159  rd=s*rs/sqrt(1+s**2)
160  dr=rd/neq
161  do i=1,neq
162  ri=dr*(0.5_dp+i-1)
163  y(i)=rs+hi-sqrt(rs**2-ri**2)
164  enddo
165  endif
166  if (viscositymodel=="fromFile") then
167  call visc_spline_ini(bblgr_res)
168  endif
169  q=1.0e-15_dp !some reasonable initial guess
170 end subroutine set_initial_conditions
171 !***********************************END****************************************
172 
173 
174 !********************************BEGINNING*************************************
178 subroutine update_domain_size(t,y)
180  use phys_prop, only: rb
181  real(dp), intent(in) :: t
182  real(dp), dimension(:), intent(in) :: y
183  integer :: neq
184  neq=size(y)
185  if (growthratemodel=="constantGrowth") then
186  rc=rc0+gr*t
187  elseif (growthratemodel=="fromFile") then
188  rc=(rb(t)+hi)/sqrt(3.0_dp)
189  endif
190  rd=rc-y(neq)/sqrt(3.0_dp)
191  dr=rd/neq
192 end subroutine update_domain_size
193 !***********************************END****************************************
194 end module model
real(dp) gam
surface tension
Definition: globals.f90:18
character(len=1024) growthratemodel
growth rate model (constantGrowth, fromFile)
Definition: globals.f90:10
real(dp), dimension(:), allocatable y
state variables
Definition: globals.f90:106
real(dp) hi
film thickness at center
Definition: globals.f90:18
real(dp) rc
total window size (radius)
Definition: globals.f90:18
character(len=1024) viscositymodel
viscosity model (constant, fromFile)
Definition: globals.f90:10
real(dp) mu
viscosity
Definition: globals.f90:18
real(dp) gr
growth rate
Definition: globals.f90:18
real(dp) rc0
initial total window size (radius)
Definition: globals.f90:18
real(dp) dstr
where strut starts in initial domain
Definition: globals.f90:18
real(dp) timestep
timestep
Definition: globals.f90:49
integer its
number of outer integration outer time steps
Definition: globals.f90:29
namespace with global variables
Definition: globals.f90:8
real(dp) rd
computational domain size (radius)
Definition: globals.f90:18
real(dp) initialtime
starting time
Definition: globals.f90:18
real(dp) dr
mesh points spacing
Definition: globals.f90:18