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
9  use globals
10  use foaming_globals_m
11  use fmodena
12  use modenastuff
13  implicit none
14  private
15  public molar_balance,kinmodel,odesystem,dim_var
16 contains
17 !********************************BEGINNING*************************************
21 subroutine odesystem (neq, t, y, ydot)
22  use phys_prop, only:rderiv
23  integer, intent(in) :: neq
24  real(dp), intent(in) :: t
25  real(dp), intent(in) :: y(neq)
26  real(dp), intent(out) :: ydot(neq)
27  integer :: i,j
28  real(dp) :: z,zw,ze,zww,zee,lamw,lame,cw,ce,cww,cee,c,dcw,dce,dil,bll
29  call dim_var(t,y)
30  call molar_balance(y)
31  ydot=0
32  if (kin_model==4) then
33  call kinmodel(y)
34  do i=1,size(kineq)
35  ydot(kineq(i))=kinsource(i)
36  enddo
37  if (w0>1e-8_dp) then
38  ydot(xweq)=-ydot(kineq(5))/w0*1.0e3_dp
39  else
40  ydot(xweq)=0
41  endif
42  ydot(xoheq)=-(ydot(kineq(2))+ydot(kineq(3)))/oh0*1.0e3_dp
43  else
44  ydot(xoheq) = aoh*exp(-eoh/rg/temp)*(1-y(xoheq))*&
45  (nco0-2*w0*y(xweq)-oh0*y(xoheq)) !polyol conversion
46  if (kin_model==3) then
47  ! gelling influence on kinetics
48  if (y(xoheq)>0.5_dp .and. y(xoheq)<0.87_dp) then
49  ydot(xoheq)=ydot(xoheq)*&
50  (-2.027_dp*y(xoheq)+2.013_dp)
51  endif
52  if (y(xoheq)>0.87_dp) then
53  ydot(xoheq)=ydot(xoheq)*(3.461_dp*y(xoheq)-2.761_dp)
54  endif
55  endif
56  if (w0>1e-3) then
57  ! water conversion
58  ! ydot(xWeq) = AW*exp(-EW/Rg/temp)*(1-y(xWeq))*&
59  ! (NCO0-2*W0*y(xWeq)-OH0*y(xOHeq)) 2nd order
60  ydot(xweq) = aw*exp(-ew/rg/temp)*(1-y(xweq)) !1st order
61  endif
62  if (dilution) then
63  if (co2_pos==1) then
64  bll=mb(2)/vsh*mbl(2)/rhop
65  else
66  bll=mb(1)/vsh*mbl(1)/rhop
67  endif
68  dil=1/(1+rhop/rhobl*bll)
69  ydot(xoheq)=ydot(xoheq)*dil
70  ydot(xweq)=ydot(xweq)*dil
71  endif
72  endif
73  !temperature (enthalpy balance)
74  ydot(teq) = -dhoh*oh0/(rhop*cp)*ydot(xoheq)-dhw*w0/(rhop*cp)*ydot(xweq)
75  do i=1,ngas
76  if (geometry=="3D") then
77  ydot(teq) = ydot(teq) - dhv(i)*12*pi*mbl(i)*d(i)*radius**4/&
78  (rhop*cp*vsh)*(y(fceq+i-1)-kh(i)*y(fpeq+i-1))/(dz(1)/2)
79  elseif (geometry=="2D") then
80  ydot(teq) = ydot(teq) - dhv(i)*4*pi*mbl(i)*d(i)*radius**2/&
81  (rhop*cp*vsh)*(y(fceq+i-1)-kh(i)*y(fpeq+i-1))/(dz(1)/2)
82  endif
83  enddo
84  if (kin_model==4) then
85  ydot(kineq(19))=ydot(teq)
86  endif
87  if (firstrun) then
88  if (inertial_term) then
89  if (geometry=="3D") then
90  ydot(req) = y(req+1) !radius (momentum balance)
91  ydot(req+1) = (sum(y(fpeq:lpeq)) + pair - pamb - &
92  2*sigma/radius - 4*eta*y(req+1)/radius - &
93  3._dp/2*y(req+1)**2)/(radius*rhop)
94  elseif (geometry=="2D") then
95  ydot(req) = y(req+1) !radius (momentum balance)
96  ydot(req+1) = (sum(y(fpeq:lpeq)) + pair - pamb - &
97  sigma/radius - 2*eta*y(req+1)/radius - &
98  3._dp/2*y(req+1)**2)/(radius*rhop)
99  endif
100  else
101  if (geometry=="3D") then
102  ydot(req) = (sum(y(fpeq:lpeq)) + pair - pamb - &
103  2*sigma/radius)*radius/(4*eta) !radius (momentum balance)
104  elseif (geometry=="2D") then
105  ydot(req) = (sum(y(fpeq:lpeq)) + pair - pamb - &
106  sigma/radius)*radius/(2*eta) !radius (momentum balance)
107  endif
108  endif
109  !partial pressure (molar balance)
110  do i=fpeq,lpeq
111  if (geometry=="3D") then
112  ydot(i) = -3*y(i)*ydot(req)/radius + y(i)/temp*ydot(teq) + &
113  9*rg*temp*d(i-fpeq+1)*radius*&
114  (y(fceq+i-fpeq)-kh(i-fpeq+1)*y(i))/(dz(1)/2)
115  elseif (geometry=="2D") then
116  ydot(i) = -2*y(i)*ydot(req)/radius + y(i)/temp*ydot(teq) + &
117  4*rg*temp*d(i-fpeq+1)*&
118  (y(fceq+i-fpeq)-kh(i-fpeq+1)*y(i))/(dz(1)/2)
119  endif
120  enddo
121  else
122  !partial pressure (molar balance)
123  do i=fpeq,lpeq
124  if (geometry=="3D") then
125  ydot(i) = -3*y(i)*rderiv(time)/radius + y(i)/temp*ydot(teq) + &
126  9*rg*temp*d(i-fpeq+1)*radius*&
127  (y(fceq+i-fpeq)-kh(i-fpeq+1)*y(i))/(dz(1)/2)
128  elseif (geometry=="2D") then
129  ydot(i) = -2*y(i)*rderiv(time)/radius + y(i)/temp*ydot(teq) + &
130  4*rg*temp*d(i-fpeq+1)*&
131  (y(fceq+i-fpeq)-kh(i-fpeq+1)*y(i))/(dz(1)/2)
132  endif
133  enddo
134  endif
135  do j=1,ngas
136  do i=1,p+1
137  if (i==1) then !bubble boundary
138  zw=0e0_dp
139  z=dz(i)/2
140  ze=dz(i)
141  zee=ze+dz(i+1)/2
142  lame=(ze-z)/(zee-z)
143  c=y(fceq+(i-1)*ngas+j-1)
144  cee=y(fceq+i*ngas+j-1)
145  cw=kh(j)*y(fpeq+j-1)
146  ce=cee*lame+c*(1-lame)
147  dcw=(c-cw)/(z-zw)
148  dce=(cee-c)/(zee-z)
149  elseif(i==p+1) then !outer boundary
150  zww=z
151  zw=ze
152  z=zee
153  ze=ze+dz(i)
154  lamw=(zw-zww)/(z-zww)
155  cww=y(fceq+(i-2)*ngas+j-1)
156  c=y(fceq+(i-1)*ngas+j-1)
157  cw=c*lamw+cww*(1-lamw)
158  ce=c
159  dcw=(c-cww)/(z-zww)
160  dce=0e0_dp
161  else
162  zww=z
163  zw=ze
164  z=zee
165  ze=ze+dz(i)
166  zee=ze+dz(i+1)/2
167  lamw=(zw-zww)/(z-zww)
168  lame=(ze-z)/(zee-z)
169  cww=y(fceq+(i-2)*ngas+j-1)
170  c=y(fceq+(i-1)*ngas+j-1)
171  cee=y(fceq+i*ngas+j-1)
172  cw=c*lamw+cww*(1-lamw)
173  ce=cee*lame+c*(1-lame)
174  dcw=(c-cww)/(z-zww)
175  dce=(cee-c)/(zee-z)
176  endif
177  !concentration (molar balance)
178  if (geometry=="3D") then
179  ydot(fceq+(i-1)*ngas+j-1) = &
180  9*d(j)*((ze+radius**3)**(4._dp/3)*dce -&
181  (zw+radius**3)**(4._dp/3)*dcw)/dz(i)
182  !reaction source
183  if (j==co2_pos) ydot(fceq+(i-1)*ngas+j-1) = &
184  ydot(fceq+(i-1)*ngas+j-1) + w0*ydot(xweq)
185  elseif (geometry=="2D") then
186  ydot(fceq+(i-1)*ngas+j-1) = &
187  4*d(j)*((ze+radius**2)*dce -&
188  (zw+radius**2)*dcw)/dz(i)
189  !reaction source
190  !WARNING: reaction source exaggerated to provide reasonable
191  !growth
192  if (j==co2_pos) ydot(fceq+(i-1)*ngas+j-1) = &
193  ydot(fceq+(i-1)*ngas+j-1) + w0*ydot(xweq)*1e4
194  endif
195  enddo
196  enddo
197 end subroutine odesystem
198 !***********************************END****************************************
199 
200 
201 !********************************BEGINNING*************************************
205 subroutine molar_balance(y)
206  real(dp), intent(in) :: y(:)
207  integer :: i,j
208  !numerical integration
209  mb=0e0_dp
210  !rectangle rule
211  do i=1,p+1
212  do j=1,ngas
213  mb(j)=mb(j)+y(fceq+j-1+(i-1)*ngas)*dz(i)
214  enddo
215  enddo
216  if (geometry=="3D") then
217  mb=mb*4*pi/3 !moles in polymer
218  elseif (geometry=="2D") then
219  mb=mb*pi !moles in polymer
220  endif
221  do i=1,ngas
222  if (geometry=="3D") then
223  mb2(i)=pressure(i)*radius**3*4*pi/(3*rg*temp) !moles in bubble
224  elseif (geometry=="2D") then
225  mb2(i)=pressure(i)*radius**2*pi/(rg*temp) !moles in bubble
226  endif
227  enddo
228  mb3=mb+mb2 !total moles
229 end subroutine molar_balance
230 !***********************************END****************************************
231 
232 
233 !********************************BEGINNING*************************************
238 subroutine dim_var(t,y)
239  use phys_prop, only:physical_properties,rb
240  real(dp), intent(in) :: t
241  real(dp), intent(in) :: y(:)
242  integer :: i
243  time=t
244  if (firstrun) then
245  radius=y(req) ! calculate bubble radius
246  else
247  radius=rb(time) ! use calculated bubble radius
248  endif
249  temp=y(teq)
250  conv=y(xoheq)
251  call physical_properties(temp,conv,radius)
252  eqconc=y(fpeq)*kh(1) !only first gas
253  do i=1,ngas
254  pressure(i)=y(fpeq+i-1)
255  enddo
256  do i=1,ngas
257  wblpol(i)=mb(i)*mbl(i)/(rhop*vsh)
258  enddo
259  avconc=mb/vsh
260  if (geometry=="3D") then
262  pair=pair0*r0**3/radius**3*temp/temp0
263  porosity=radius**3/(radius**3+s0**3-r0**3)
264  st=(s0**3+radius**3-r0**3)**(1._dp/3)-radius !thickness of the shell
265  elseif (geometry=="2D") then
267  pair=pair0*r0**2/radius**2*temp/temp0
268  porosity=radius**2/(radius**2+s0**2-r0**2)
269  st=(s0**2+radius**2-r0**2)**(1._dp/2)-radius !thickness of the shell
270  endif
271  rhofoam=(1-porosity)*rhop
272  bub_pres=sum(pressure)+pair-pamb
273 end subroutine dim_var
274 !***********************************END****************************************
275 
276 
277 !********************************BEGINNING*************************************
282 subroutine kinmodel(y)
283  real(dp), intent(in) :: y(:)
284  integer :: i
285  if (kin_model==4) then
286  do i=1,size(kineq)
287  call modena_inputs_set(kininputs, kininputspos(i+1), y(kineq(i)))
288  enddo
289  endif
290  call modena_inputs_set(kininputs, kininputspos(1), time)
291  call modena_inputs_set(kininputs, kininputspos(20), y(teq)-273.15_dp)
292  ret = modena_model_call(kinmodena, kininputs, kinoutputs)
293  if(ret /= 0) then
294  call exit(ret)
295  endif
296  if (kin_model==4) then
297  kinsource=0
298  do i=1,size(kineq)
299  kinsource(i) = modena_outputs_get(kinoutputs, kinoutputspos(i))
300  enddo
301  endif
302 end subroutine kinmodel
303 !***********************************END****************************************
304 end module model
real(dp) porosity
foam porosity
Definition: globals.f90:49
real(dp), dimension(:), allocatable dhv
evaporation heat of blowing agent (for each gas)
Definition: globals.f90:106
integer teq
temperature equation (index)
Definition: globals.f90:29
real(dp) st
shell thickness
Definition: globals.f90:49
integer ngas
number of dissolved gases
Definition: globals.f90:29
real(dp) rhop
polymer density
Definition: globals.f90:49
real(dp) temp
temperature (K)
Definition: globals.f90:49
real(dp) aw
frequential factor of blowing reaction
Definition: globals.f90:49
integer req
radius equation (index)
Definition: globals.f90:29
real(dp) pair0
initial partial pressure of air
Definition: globals.f90:49
real(dp) radius
bubble radius (m)
Definition: globals.f90:49
real(dp), dimension(:), allocatable kh
Henry constants (for each dissolved gas)
Definition: globals.f90:106
real(dp) aoh
frequential factor of gelling reaction
Definition: globals.f90:49
real(dp), dimension(:), allocatable mb2
moles in bubble
Definition: globals.f90:106
real(dp) w0
initial concentration of water (can be zero)
Definition: globals.f90:49
logical dilution
use dilution effect for kinetics (t/f)
Definition: globals.f90:22
real(dp), dimension(:), allocatable dz
spatial discretization
Definition: globals.f90:106
real(dp), dimension(:), allocatable pressure
partial pressure(Pa)
Definition: globals.f90:106
real(dp), dimension(:), allocatable kinsource
kinetic source term
Definition: globals.f90:106
real(dp) s0
initial shell thickness
Definition: globals.f90:49
real(dp) laplace_pres
Laplace pressure (Pa)
Definition: globals.f90:49
logical inertial_term
include inertial term in equations (t/f)
Definition: globals.f90:22
real(dp) sigma
interfacial tension
Definition: globals.f90:49
real(dp) rhobl
density of liquid physical blowing agent
Definition: globals.f90:49
real(dp), dimension(:), allocatable mbl
blowing agent molar mass (for each dissolved gas)
Definition: globals.f90:106
real(dp) eoh
activation energy of gelling reaction
Definition: globals.f90:49
real(dp) eqconc
equivalent concentration for first gas
Definition: globals.f90:49
real(dp) conv
conversion of polyol
Definition: globals.f90:49
real(dp) time
time (s)
Definition: globals.f90:49
character(len=99) geometry
geometry 3D=spherical, 2D=cylindrical
Definition: globals.f90:11
integer, dimension(:), allocatable kineq
kinetics state variable equations (indexes)
Definition: globals.f90:102
real(dp) nco0
initial concentration of isocyanate
Definition: globals.f90:49
real(dp), dimension(:), allocatable mb3
total moles
Definition: globals.f90:106
integer lpeq
last pressure equation (index)
Definition: globals.f90:29
real(dp) rhofoam
foam density
Definition: globals.f90:49
real(dp) temp0
initial temperature
Definition: globals.f90:49
integer co2_pos
carbon dioxide position
Definition: globals.f90:29
real(dp), dimension(:), allocatable d
diffusion coefficients (for each dissolved gas)
Definition: globals.f90:106
real(dp), dimension(:), allocatable avconc
average concentration in reaction mixture
Definition: globals.f90:106
real(dp), dimension(:), allocatable mb
moles in polymer
Definition: globals.f90:106
real(dp) pamb
ambient pressure (in the liquid)
Definition: globals.f90:49
real(dp) vsh
shell volume
Definition: globals.f90:49
integer kin_model
reaction kinetics model.
Definition: globals.f90:29
real(dp) eta
viscosity
Definition: globals.f90:49
real(dp), dimension(:), allocatable wblpol
weight fraction of blowing agents in reaction mixture
Definition: globals.f90:106
real(dp) cp
heat capacity of the reaction mixture
Definition: globals.f90:49
integer fceq
first concentration equation (index)
Definition: globals.f90:29
integer xoheq
polyol conversion equation (index)
Definition: globals.f90:29
real(dp) r0
initial radius
Definition: globals.f90:49
integer fpeq
first pressure equation (index)
Definition: globals.f90:29
real(dp) dhw
blowing reaction enthalpy
Definition: globals.f90:49
namespace with global variables
Definition: globals.f90:8
real(dp) pair
partial pressure of air
Definition: globals.f90:49
integer p
number of internal nodes
Definition: globals.f90:29
real(dp) dhoh
gelling reaction enthalpy
Definition: globals.f90:49
real(dp) oh0
initial concentration of polyol (don&#39;t set to zero)
Definition: globals.f90:49
real(dp) ew
activation energy of blowing reaction
Definition: globals.f90:49
integer xweq
water conversion equation (index)
Definition: globals.f90:29