MoDeNa  1.0
Software framework facilitating sequential multi-scale modelling
tests.f90
Go to the documentation of this file.
1 
7 module tests
8  use constants
9  use ioutils
10  use foamprop, only: effrad
11  use foamgeom, only: foam_morpholgy
12  use conduction, only: effcond
13  use condrad, only: equcond,cond,alpha,sigma
14  implicit none
15  private
16  public loadparameters,eqcond,eqcond_por,eqcond_dcell,eqcond_strut
17  character(len=99) :: fileplacein_par='./inputs/' !modena
18  character(len=99) :: fileplacein_ref='../spectra/' !modena
19  character(len=99) :: fileplaceout='./' !modena
20  character(len=99) :: inputs='foamConductivity.json',spectra='spectra.out'
21  character(len=99) :: nspec='spec_n.in'
22  character(len=99) :: kspec='spec_k.in'
23  character(len=99) :: gasspec='gasspec.in'
24  character(len=99) :: after_foaming,after_foaming0='after_foaming.txt'
25  character(len=99) :: bg_res='../../foamExpansion/results/bubbleGrowth/'
26  character(len=99) :: qmom0d_res='../../foamExpansion/results/CFD0D/'
27  character(len=99) :: qmom3d_res='../../foamExpansion/results/CFD3D/'
28 contains
29 !********************************BEGINNING*************************************
31 subroutine eqcond(regions)
32 
33  integer, intent(in) :: regions
34  integer :: i,j,fi
35  real(dp), dimension(:), allocatable :: regbound,regcond
36  real(dp), dimension(:,:), allocatable :: regalpha,regsigma
37  allocate(regbound(regions+1),regcond(regions),regalpha(regions,nbox),&
38  regsigma(regions,nbox),alpha(nz,nbox),sigma(nz,nbox),cond(nz))
39  do i=1,regions+1
40  regbound(i)=(i-1)*dfoam/regions
41  enddo
42  do i=1,regions
43  if (por < 0.8_dp) then
44  write(*,*) 'Radiative prop. not calculated for porosity < 0.8'
45  write(mfi,*) 'Radiative prop. not calculated for porosity < 0.8'
46  krad=2e-3_dp
47  call effcond
48  open(newunit(fi),file='foamConductivity.out')
49  write(fi,*) eqc_ross
50  close(fi)
51  return
52  endif
53  call foam_morpholgy
54  if (testmode) then
55  write(*,*) 'TESTING: radiative properties not calculated.'
56  write(*,*) 'Disable test mode if you want more reasonable results.'
57  krad=2e-3_dp
58  call effcond
59  open(newunit(fi),file='foamConductivity.out')
60  write(fi,*) eqc_ross
61  close(fi)
62  return
63  endif
64  call effrad(spectra)
65  call effcond
66  regcond(i)=effc
67  regalpha(i,:)=abscoeffbox
68  regsigma(i,:)=scattcoeffbox
69  deallocate(abscoeffbox,scattcoeffbox)
70  enddo
71  do i=1,nz
72  do j=1,regions+1
73  if ((i-0.5_dp)*dfoam/nz<regbound(j)) exit
74  enddo
75  j=j-1
76  cond(i)=regcond(j)
77  alpha(i,:)=regalpha(j,:)
78  sigma(i,:)=regsigma(j,:)
79  enddo
80  call equcond
81  deallocate(regbound,regcond,regalpha,regsigma,alpha,sigma,cond)
82 end subroutine eqcond
83 !***********************************END****************************************
84 
85 
86 !********************************BEGINNING*************************************
88 subroutine eqcond_por
89  integer :: fi,npoints,i
90  real(dp) :: pormin,pormax,dpor
91  pormin=0.90_dp
92  pormax=0.995_dp
93  npoints=20
94  dpor=(pormax-pormin)/(npoints-1)
95  open(newunit(fi),file='eqcond_por.csv')
96  write(fi,*) 'porosity,foam_density,eq_cond,Ross_eq_cond,&
97  kgas,ksol,krad'
98  do i=1,npoints
99  por=pormin+(i-1)*dpor
100  call eqcond(1)
101  write(fi,'(1x,es23.15,7(",",es23.15))') &
102  por,rhof,eqc,eqc_ross,kgas,ksol,krad
103  write(*,*)
104  write(mfi,*)
105  enddo
106  close(fi)
107 end subroutine eqcond_por
108 !***********************************END****************************************
109 
110 
111 !********************************BEGINNING*************************************
113 subroutine eqcond_dcell
114  integer :: fi,npoints,i
115  real(dp) :: dcellmin,dcellmax,ddcell
116  dcellmin=1e-6_dp
117  dcellmax=1000e-6_dp
118  npoints=7
119  ddcell=log10(dcellmax/dcellmin)/(npoints-1)
120  open(newunit(fi),file='eqcond_dcell.out')
121  write(fi,'(1000A23)') '#porosity','eq. conductivity'
122  do i=1,npoints
123  dcell=dcellmin*10**((i-1)*ddcell)
124  call eqcond(1)
125  write(fi,'(1000es23.15)') dcell,eqc
126  enddo
127  close(fi)
128 end subroutine eqcond_dcell
129 !***********************************END****************************************
130 
131 
132 !********************************BEGINNING*************************************
134 subroutine eqcond_strut
135  integer :: fi,npoints,i
136  real(dp) :: strutmin,strutmax,dstrut
137  strutmin=0.0_dp
138  strutmax=0.9_dp
139  npoints=19
140  dstrut=(strutmax-strutmin)/(npoints-1)
141  open(newunit(fi),file='eqcond_strut.out')
142  write(fi,'(1000A23)') '#strut content','eq. conductivity','Ross. eq. cond.'
143  do i=1,npoints
144  fs=strutmin+(i-1)*dstrut
145  call eqcond(1)
146  write(fi,'(1000es23.15)') fs,eqc,eqc_ross
147  enddo
148  close(fi)
149 end subroutine eqcond_strut
150 !***********************************END****************************************
151 
152 
153 !********************************BEGINNING*************************************
155 subroutine loadparameters
156  use physicalproperties
157  use fson
158  use fson_value_m, only: fson_value_get
159  type(fson_value), pointer :: json_data
160  integer :: fi,ios,i,j
161  logical :: file_exists
162  real(dp) :: xO2,xN2,xCO2,xCyP,matr(7)
163  character(len=80) :: strval !name of the file with morphology
164  inputs=trim(adjustl(fileplacein_par))//trim(adjustl(inputs))
165  inquire(file=inputs,exist=file_exists) !first try current folder
166  if (.not. file_exists) then
167  inputs='../'//inputs !then try one folder up
168  inquire(file=inputs,exist=file_exists)
169  if (.not. file_exists) stop 'input file not found'
170  endif
171  spectra=trim(adjustl(fileplaceout))//trim(adjustl(spectra))
172  json_data => fson_parse(inputs)
173  call fson_get(json_data, "upperBoundary.temperature", temp1)
174  call fson_get(json_data, "lowerBoundary.temperature", temp2)
175  call fson_get(json_data, "upperBoundary.emittance", emi1)
176  call fson_get(json_data, "lowerBoundary.emittance", emi2)
177  call fson_get(json_data, "gasDensity", rhog)
178  call fson_get(json_data, "solidDensity", rhos)
179  call fson_get(json_data, "sourceOfProperty.porosity", strval)
180  if (strval=="BubbleGrowth") then
181  after_foaming=trim(adjustl(bg_res))//trim(adjustl(after_foaming0))
182  open(unit=newunit(fi),file=after_foaming)
183  read(fi,*)
184  read(fi,*) matr(1:4)
185  rhof=matr(1)
186  por=1-rhof/rhos
187  close(fi)
188  elseif (strval=="Qmom0D") then
189  after_foaming=trim(adjustl(qmom0d_res))//trim(adjustl(after_foaming0))
190  open(unit=newunit(fi),file=after_foaming)
191  read(fi,*)
192  read(fi,*) matr(1:4)
193  rhof=matr(1)
194  por=1-rhof/rhos
195  close(fi)
196  elseif (strval=="Qmom3D") then
197  after_foaming=trim(adjustl(qmom3d_res))//trim(adjustl(after_foaming0))
198  open(unit=newunit(fi),file=after_foaming)
199  read(fi,*)
200  read(fi,*) matr(1:4)
201  rhof=matr(1)
202  por=1-rhof/rhos
203  close(fi)
204  elseif (strval=="DirectInput") then
205  call fson_get(json_data, "porosity", por)
206  else
207  write(*,*) 'unknown source for porosity'
208  stop
209  endif
210  rhof=(1-por)*rhos
211  call fson_get(json_data, "sourceOfProperty.cellSize", strval)
212  if (strval=="BubbleGrowth") then
213  after_foaming=trim(adjustl(bg_res))//trim(adjustl(after_foaming0))
214  open(unit=newunit(fi),file=after_foaming)
215  read(fi,*)
216  read(fi,*) matr(1:4)
217  dcell=matr(2)
218  close(fi)
219  elseif (strval=="Qmom0D") then
220  after_foaming=trim(adjustl(qmom0d_res))//trim(adjustl(after_foaming0))
221  open(unit=newunit(fi),file=after_foaming)
222  read(fi,*)
223  read(fi,*) matr(1:4)
224  dcell=matr(2)
225  close(fi)
226  elseif (strval=="Qmom3D") then
227  after_foaming=trim(adjustl(qmom3d_res))//trim(adjustl(after_foaming0))
228  open(unit=newunit(fi),file=after_foaming)
229  read(fi,*)
230  read(fi,*) matr(1:4)
231  dcell=matr(2)
232  close(fi)
233  elseif (strval=="DirectInput") then
234  call fson_get(json_data, "cellSize", dcell)
235  else
236  write(*,*) 'unknown source for cell size'
237  stop
238  endif
239  call fson_get(json_data, "sourceOfProperty.gasComposition", strval)
240  if (strval=="BubbleGrowth") then
241  after_foaming=trim(adjustl(bg_res))//trim(adjustl(after_foaming0))
242  open(unit=newunit(fi),file=after_foaming)
243  read(fi,*)
244  read(fi,*) matr(1:4)
245  xo2=0
246  xn2=0
247  xcyp=matr(3)
248  xco2=matr(4)
249  xcyp=xcyp/(xcyp+xco2)
250  xco2=1-xcyp
251  close(fi)
252  elseif (strval=="Qmom0D") then
253  after_foaming=trim(adjustl(qmom0d_res))//trim(adjustl(after_foaming0))
254  open(unit=newunit(fi),file=after_foaming)
255  read(fi,*)
256  read(fi,*) matr(1:4)
257  xo2=0
258  xn2=0
259  xcyp=matr(3)
260  xco2=matr(4)
261  xcyp=xcyp/(xcyp+xco2)
262  xco2=1-xcyp
263  close(fi)
264  elseif (strval=="Qmom3D") then
265  after_foaming=trim(adjustl(qmom3d_res))//trim(adjustl(after_foaming0))
266  open(unit=newunit(fi),file=after_foaming)
267  read(fi,*)
268  read(fi,*) matr(1:4)
269  xo2=0
270  xn2=0
271  xcyp=matr(3)
272  xco2=matr(4)
273  xcyp=xcyp/(xcyp+xco2)
274  xco2=1-xcyp
275  close(fi)
276  elseif (strval=="DirectInput") then
277  call fson_get(json_data, "gasComposition.O2", xo2)
278  call fson_get(json_data, "gasComposition.N2", xn2)
279  call fson_get(json_data, "gasComposition.CO2", xco2)
280  call fson_get(json_data, "gasComposition.Cyclopentane", xcyp)
281  else
282  write(*,*) 'unknown source for gas composition'
283  stop
284  endif
285  call fson_get(json_data, "sourceOfProperty.strutContent", strval)
286  if (strval=="StrutContent") then
287  call strutcontent(fs,rhof)
288  elseif (strval=="DirectInput") then
289  call fson_get(json_data, "strutContent", fs)
290  else
291  write(*,*) 'unknown source for strut content'
292  stop
293  endif
294  call fson_get(json_data, "sourceOfProperty.wallThickness", strval)
295  if (strval=="DirectInput") then
296  call fson_get(json_data, "wallThickness", dwall)
297  else
298  write(*,*) 'unknown source for wall thickness'
299  stop
300  endif
301  call fson_get(json_data, "morphologyInput", strval)
302  if (strval=="wallThickness") then
303  morph_input=1
304  elseif (strval=="strutContent") then
305  morph_input=2
306  elseif (strval=="strutSize") then
307  morph_input=3
308  elseif (strval=="strutContent2") then
309  morph_input=4
310  else
311  write(*,*) 'unknown choice of morphologyInput'
312  stop
313  endif
314  call fson_get(json_data, "strutSize", dstrut)
315  call fson_get(json_data, "foamThickness", dfoam)
316  call fson_get(json_data, "spatialDiscretization", nz)
317  call fson_get(json_data, "useWallThicknessDistribution", wdist)
318  if (wdist) then
319  call fson_get(json_data, "wallThicknessStandardDeviation", wsdev)
320  endif
321  call fson_get(json_data, "numberOfGrayBoxes", nbox)
322  call fson_get(json_data, "numericalEffectiveConductivity", numcond)
323  if (numcond) then
324  call fson_get(json_data, "structureName", structurename)
325  endif
326  call fson_get(json_data, "testMode", testmode)
327  if (temp1<temp2) then
328  tmean=temp1
329  temp1=temp2
330  temp2=tmean
331  endif
332  tmean=(temp1+temp2)/2
333  call gasconductivity(cond1,tmean,xo2,xn2,xco2,xcyp)
334  call polymerconductivity(cond2,tmean)
335  n1=1
336  k1=0
337  write(*,*) 'System information:'
338  write(*,'(2x,A,1x,es9.3,1x,A)') 'higher temperature:',temp1,'K'
339  write(*,'(2x,A,1x,es9.3,1x,A)') 'lower temperature: ',temp2,'K'
340  write(*,*) 'Phase properties:'
341  write(*,'(2x,A,1x,es9.3,1x,A)') 'gas conductivity: ',cond1*1e3_dp,'mW/m/K'
342  write(*,'(2x,A,1x,es9.3,1x,A)') 'solid conductivity:',cond2*1e3_dp,'mW/m/K'
343  write(mfi,*) 'System information:'
344  write(mfi,'(2x,A,1x,es9.3,1x,A)') 'higher temperature:',temp1,'K'
345  write(mfi,'(2x,A,1x,es9.3,1x,A)') 'lower temperature: ',temp2,'K'
346  write(mfi,*) 'Phase properties:'
347  write(mfi,'(2x,A,1x,es9.3,1x,A)') &
348  'gas conductivity: ',cond1*1e3_dp,'mW/m/K'
349  write(mfi,'(2x,A,1x,es9.3,1x,A)') &
350  'solid conductivity:',cond2*1e3_dp,'mW/m/K'
351 
352  j=0
353  open(newunit(fi),file=trim(adjustl(fileplacein_ref))//trim(adjustl(nspec)))
354  do !find number of points
355  read(fi,*,iostat=ios)
356  if (ios/=0) exit
357  j=j+1
358  enddo
359  rewind(fi)
360  allocate(lambdan(j),nwl(j))
361  do i=1,j
362  read(fi,*) lambdan(i),nwl(i)
363  enddo
364  lambdan=lambdan*1e-6_dp
365  close(fi)
366 
367  j=0
368  open(newunit(fi),file=trim(adjustl(fileplacein_ref))//trim(adjustl(kspec)))
369  do !find number of points
370  read(fi,*,iostat=ios)
371  if (ios/=0) exit
372  j=j+1
373  enddo
374  rewind(fi)
375  allocate(lambdak(j),kwl(j))
376  do i=1,j
377  read(fi,*) lambdak(i),kwl(i)
378  enddo
379  lambdak=lambdak*1e-6_dp
380  close(fi)
381 
382  j=0
383  open(newunit(fi),&
384  file=trim(adjustl(fileplacein_ref))//trim(adjustl(gasspec)))
385  do !find number of points
386  read(fi,*,iostat=ios)
387  if (ios/=0) exit
388  j=j+1
389  enddo
390  rewind(fi)
391  allocate(lambdagas(j),acgas(j))
392  do i=1,j
393  read(fi,*) lambdagas(i),acgas(i)
394  enddo
395  lambdagas=lambdagas*1e-6_dp
396  close(fi)
397 end subroutine loadparameters
398 !***********************************END****************************************
399 end module tests