c------------------------------------------------------------------------------ c ... code to prepare tables of transport coefficients c ... flag: in_n2 has the following purpose c ... in_n2 = .false. ==> transport properties are evaluatedased on c ... the 1D flame mixture composition c ... (of course the binary diffusion coefficients c ... are D_i_N2, but given the rest of the mixture) c ... so: amu(T) = amu_1D-flame-mixture (T) c ... htcond(T) = htcond_1D-flame-mixture (T) c ... cp(T) = cp_1D-flame-mixture (T) c ... c ... in_n2 = .true. ==> transport properties are evaluated based on c ... an N2 gas only. c ... so: amu(T) = amu_N2 (T) c ... htcond(T) = htcond_N2 (T) c ... cp(T) = cp_N2 (T) c ... c------------------------------------------------------------------------------ c ... unaffected by in_n2: are: c ... cpsp_k (T), hsp_k (T), gsp_k (T) c ... capd_k(T) = capd_k_N2 (T) binary diffusion coeff. indep of mixture c ... anyway. At any rate, mechanism of in_n2 coded in gcapd also. c ... gcapd gives identical answers for in_n2 false or true c------------------------------------------------------------------------------ c ... nb. cp (T) is evaluated but not used by dflame c ... so the only meaningful result of in_n2=.true. is to change c ... the tabulate/used transport coefficients for momentum and heat c ... namely: mu (viscosity) and lambda (thermal conductivity) of the c ... mixture c------------------------------------------------------------------------------ subroutine dfit(temp_min,temp_max) IMPLICIT NONE include 'parameter.par' include 'common.com' integer i_n2, k ,kk double precision temp_min,temp_max,tv,vtemp character*80 fmt c------------------------------------------------------------------------------- c ... read chemistry input file and initialize chemical data bases call cheminit call setcon c------------------------------------------------------------------------------- c ... read input data call init ! initialize c------------------------------------------------------------------------------ c ... evaluate detailed transport and thermodynamic properties c ... these are dimensional quantities in SI units call getmu ! get amu(j), j=1,2,...,n call gthtcond ! get htcond(j), j=1,2,...,n call getcpsp ! get cpsp(j,k), j=1,2,...,n, k=1,2,...,nsp call getcp ! get cp(j), j=1,2,...,n call gcapd ! get D(j,k)_nsp, j=1,2,...,n, k=1,2,...,nsp call gethsp ! get hsp(j,k), j=1,2,...,n, k=1,2,...,nsp call getgsp ! get gsp(j,k), j=1,2,...,n, k=1,2,...,nsp c------------------------------------------------------------------------------ c ... writeout write(*,*)' writing out data' c------------------------------------------------------------------------------ c------------------------------------------------------------------------------ c ... fit each property against temperature c------------------------------------------------------------------------------ c------------------------------------------------------------------------------ c ... set the span of the tabulation of temperature t1 = temp_min t2 = temp_max c ... set the number of points in the table based on a specified dt dt = 0.1 c dt = 1.0 !Use this when making tables for the demo ng = nint((t2-t1)/dt)+1 if (ng.gt.ntabmx) then write(*,*) 'dfit: Error you need to increase ntabmx or dicrease ' write(*,*) 'the temperature range' endif nc = ng - 1 c ... tabulate temperature do k=1,ng tv = t1 + dble(k-1)*dt ttab(k) = tv end do c------------------------------------------------------------------------------ c ... fit cp_k(T) open(unit=50,file='cpsp.tab',status='unknown') write(50,'(''# 1:T 2:cp_1 3:cp_2 ... nsp+1:cp_nsp '')') write(50,'(''# '',e22.14)')dt write(50,'(''# '',2i9)')ng,nsp+1 do k=1,ng vtemp = ttab(k) call getcpor(vtemp,nsp,cpspj) do kk=1,nsp cpspj(kk) = cpspj(kk)*rg(kk) end do write(fmt, '(a,i3,a)') '(',nsp+1,'e22.14)' write(50,fmt)ttab(k),(cpspj(kk),kk=1,nsp) end do close(50) c------------------------------------------------------------------------------ c ... fit h_k (T) open(unit=50,file='hk.tab',status='unknown') write(50,'(''# 1:T 2:h_1 3:h_2 ... nsp+1:h_nsp'')') write(50,'(''# '',e22.14)')dt write(50,'(''# '',2i9)')ng,nsp+1 do k=1,ng vtemp = ttab(k) call gethort(vtemp,nsp,hspj) do kk=1,nsp hspj(kk) = hspj(kk)*rg(kk)*vtemp end do write(fmt, '(a,i3,a)') '(',nsp+1,'e22.14)' write(50,fmt)ttab(k),(hspj(kk),kk=1,nsp) end do close(50) c------------------------------------------------------------------------------ c ... fit g_k (T) open(unit=50,file='gk.tab',status='unknown') write(50,'(''# 1:T 2:g_1 3:g_2 ... nsp+1:g_nsp'')') write(50,'(''# '',e22.14)')dt write(50,'(''# '',2i9)')ng,nsp+1 do k=1,ng vtemp = ttab(k) call getgibbs(vtemp,nsp,gspj) write(fmt, '(a,i3,a)') '(',nsp+1,'e22.14)' write(50,fmt)ttab(k),(gspj(kk),kk=1,nsp) end do close(50) c------------------------------------------------------------------------------ return end c*******************************************************************************