PlasCom2  1.0
XPACC Multi-physics simluation application
InitialY4.f90
Go to the documentation of this file.
2 
3  use modexamplescommon
4  use modbc
5  use modparsearguments
6  use modstdio
7  use modplot3d_io
8  implicit none
9 
10  integer(ik) :: i, j, k
11  character(len=CMD_ARG_LENGTH), dimension(:), allocatable :: RawArguments
12  type(t_cmd_opt), dimension(12) :: Options
13  integer(ik) :: Nx, Ny
14  integer(ik) :: OutputFormat
15  real(rk) :: U, V
16  real(rk),dimension(:,:), allocatable :: xfac, yfac
17  integer(ik) :: i1, j1, k1, i2, j2, k2, IBcheck
18  real(rk) :: rhoinv
19  character(120) :: ExecPath,GridPath,SolPath
20  character :: cmd*100
21  integer(ik), dimension(2) :: nPoints
22  real(rk), dimension(2) :: Length
23  real(rk), dimension(:,:,:), allocatable :: X
24  real(rk), dimension(:,:,:,:,:), pointer :: XTemp, QTemp, QauxTemp
25  integer(ik), dimension(:,:), allocatable :: IB
26  integer(ik), dimension(:,:,:,:), pointer :: SSIB
27  real(rk), dimension(:,:,:), allocatable :: Q, Qaux,massFractions
28  type(t_bc), dimension(:),allocatable :: BCs
29  real(rk), parameter :: Gamma = 1.4_rk
30  real (rk), parameter :: GasConstant = 8314.4621_rk !J/(K kmol)
31  real(rk) :: YO2, YH2, YH, YH2O, YHO2, nitrogenOxygenMoleRatio
32  real(rk) :: MwRef, Mwa
33  real(rk) :: MachFactor,GL_csq
34  real(rk) :: xtilde, ytilde!, Vtemp
35  real(rk) :: Density, DensInv, Lref
36  real(rk) :: Ly,Lx
37  real(rk), dimension(2) :: Velocity
38  integer(ik), dimension(2) :: nSponge
39  real(rk), dimension(:), allocatable :: Mwcoeff, MwcoeffInv
40  Integer (ik) :: VolRateSpecified = 0
41  real(rk)::exp_x,exp_y
42  integer(ik)::useDimensional
43 
44  real(rk), dimension(:), allocatable :: thermo_mwts
45  real(rk), dimension(:), allocatable :: thermo_h0,thermo_cp0,thermo_Y
46  real(rk) :: thermo_rho, thermo_p, thermo_e, thermo_h, thermo_T, thermo_rhoe
47  real(rk) :: densRef, Rair
48 
49  Integer (ik), parameter :: nspecies=8
50  Integer (ik), parameter :: iH2 = 1
51  Integer (ik), parameter :: iO2 = 2
52  Integer (ik), parameter :: iH = 3
53  Integer (ik), parameter :: iH2O = 4
54  Integer (ik), parameter :: iHO2 = 5
55  Integer (ik), parameter :: iH2O2 = 6
56  Integer (ik), parameter :: iO = 7
57  Integer (ik), parameter :: iOH = 8
58  Integer (ik) :: iN2 =9
59  Integer (ik), parameter :: GridStretch = 1
60  Integer (ik), parameter :: includeElectrode = 1
61 
62  integer(ik)::iplug,jplug
63  integer(ik)::jSlottedJetStart,jSlottedJetEnd
64  real(rk)::AmbientPressure,AmbientDensity
65  real(rk),dimension(:,:),allocatable::P ,T
66  integer(ik)::jSpongeInlet
67  integer(ik)::jm
68  real(rk)::ystartJet,yendJet,ymid,y
69  integer(ik),parameter::Nrefine=1
70  real(rk),parameter::ReferenceLength=1.0
71  real(rk)::xplug,xpos
72  integer(ik),parameter::depthSlottedJet=20
73  real(rk)::Mjet
74  real(rk):: CPR
75  real(rk):: CDR
76  real(rk):: Po
77  real(rk):: rhoo
78  real(rk):: Pjet
79  real(rk):: rhojet
80 
81  real(rk)::plugRadius
82  real(rk)::slotWidth
83  real(rk)::dx,dy
84  real(rk)::machCrossStream
85 
86  real(rk)::Tref,rhoref,cref,rhoYO2Ref,rhoH2ref,DensityRatio
87  real(rk)::Lp,dummyVal
88  character(len=1000)::filename,dummyline
89  integer::s,nskip
90  logical::AIR_INTO_AIR, HYDROGEN_INTO_AIR
91  integer::jetStart
92  real(rk)::uvel,vvel
93 
94  real(rk)::tmp,tmp2,pressure,temperature
95  real(rk)::MwcoeffRho
96 
97  real(rk)::densityLIBREF,temperatureLIBREF,velocityLIBREF
98  real(rk)::densityLIB,vvelLIB,uvelLIB,temperatureLIB,YOLIB,YO2LIB,YO2LIBREF
99 
100  integer :: SSptsX, SSptsY, SSNdim, SSngrid, SSftype, SSNvar
101  Character(LEN=2) :: SSprec, SSgf, SSvf, SSiblocal
102  real(rk) :: SStau(4)
103  integer,pointer,dimension(:,:) :: SSND
104  integer,allocatable,dimension(:,:) :: ND
105 
106  real(rk)::unstartLoc
107 
108  real(rk):: MachNumberPreShock
109  real(rk):: DensityPreShock
110  real(rk):: TemperaturePreShock
111  real(rk):: SoundSpeedPreShock
112 
113  real(rk):: MachNumberPostShock
114  real(rk):: DensityPostShock
115  real(rk):: TemperaturePostShock
116  real(rk):: SoundSpeedPostShock
117 
118  real(rk)::VerticalOffSetFromJet
119  real(rk)::HorizontalOffSetFromCenterline
120  integer::jSlotJetCenter,iPlaceLIB,jPlaceLIB
121 
122  !inputs from Gyu Sub [labeled GS]
123  real(rk),parameter::airPoGS=167.1_rk*1.e3 !kPa
124  real(rk),parameter::airToGs=298.0_rk !Kelvin
125  real(rk),parameter::fuelPoGS=386.6_rk*1.e3 !kPa
126  real(rk),parameter::fuelToGS=298.0_rk !Kelvin
127  real(rk),parameter::airMdotGS=56.38_rk !g/s
128  real(rk),parameter::fuelMdotGS=1.842_rk !g/s
129  real(rk)::airRoGS,fuelRoGs,airCoGS,fuelCoGs !derived below from Gyu Sub data
130  real(rk),parameter::testSectionMachNumber=2.7_rk
131  real(rk)::testSectionDensity,testSectionPressure,testSectionTemperature,testSectionSoundSpeed,testSectionVelocity
132  real(rk),parameter::fuelMachNumber=1.0_rk
133  real(rk)::fuelDensity,fuelPressure,fuelTemperature,fuelSoundSpeed,fuelVelocity
134 
135  !to nondimensionalize the pressure and temperature
136  real(rk),parameter::nondimT=298.*(gamma-1.0)
137  real(rk),parameter::nondimP=101.325 !kPa
138  real(rk),parameter::nondimR=1.2041 !kg/m^3 !what was in the input deck
139  real(rk),parameter::nondimVel=343. !m/s
140 
141  airrogs = airpogs / airtogs / 259.8 !indiviaul gas constant for oxygen [259.8]
142  fuelrogs = fuelpogs / fueltogs / 4124. !individual gas constant for hydrogen [4124]
143  aircogs = sqrt(gamma * airpogs / airrogs)
144  fuelcogs = sqrt(gamma * fuelpogs / fuelrogs)
145 
146  print *,"**************************************************************"
147  print *,"Print the Gyu Sub inputs"
148  print *,"airPo [Pa] = ",airpogs
149  print *,"airTo [K] = ",airtogs
150  print *,"airRo [kg/m^3] (derived) = ",airrogs
151  print *,"fuelPo [Pa] = ",fuelpogs
152  print *,"fuelTo [K] = ",fueltogs
153  print *,"fuelRo [kg/m^3] (derived) = ",fuelrogs
154  print *,"**************************************************************"
155 
156  testsectiondensity=get_isentropic_density(testsectionmachnumber,airrogs,gamma)
157  testsectionpressure=get_isentropic_pressure(testsectionmachnumber,airpogs,gamma)
158  testsectiontemperature=get_isentropic_temperature(testsectionmachnumber,airtogs,gamma)
159  testsectionsoundspeed=get_isentropic_soundspeed(testsectionmachnumber,aircogs,gamma)
160  testsectionvelocity=testsectionmachnumber*testsectionsoundspeed
161 
162  print *,"**************************************************************"
163  print *,"Print isentropic values in test section (M=2.7)"
164  print *,"testSectionP [Pa] (derived) = ",testsectionpressure
165  print *,"testSectionT [K] (derived) = ",testsectiontemperature
166  print *,"testSectionR [kg/m^3] (derived) = ",testsectiondensity
167  print *,"testSectionVel [m/s] (derived) = ",testsectionvelocity
168  print *,"Recheck Mach = ",testsectionvelocity/testsectionsoundspeed
169  print *,"**************************************************************"
170 
171  fueldensity=get_isentropic_density(fuelmachnumber,fuelrogs,gamma)
172  fuelpressure=get_isentropic_pressure(fuelmachnumber,fuelpogs,gamma)
173  fueltemperature=get_isentropic_temperature(fuelmachnumber,fueltogs,gamma)
174  fuelsoundspeed=get_isentropic_soundspeed(fuelmachnumber,fuelcogs,gamma)
175  fuelvelocity=fuelmachnumber*fuelsoundspeed
176 
177  print *,"**************************************************************"
178  print *,"Print isentropic values exiting fuel (M=1.0)"
179  print *,"fuelP [Pa] (derived) = ",fuelpressure
180  print *,"fuelT [K] (derived) = ",fueltemperature
181  print *,"fuelR [kg/m^3] (derived) = ",fueldensity
182  print *,"fuelVel [m/s] (derived) = ",fuelvelocity
183  print *,"Recheck Mach = ",fuelvelocity/fuelsoundspeed
184  print *,"**************************************************************"
185 
186  print *,"**************************************************************"
187  print *,"Momentum Ratio of Test Section to Jet"
188  print*,"J=",fueldensity*fuelvelocity**2/testsectiondensity/testsectionvelocity**2
189  print *,"**************************************************************"
190 
191  print *,"**************************************************************"
192  print *,"Stagnation jet pressure to ambient test section pressure"
193  print*,"PR=",fuelpogs/testsectionpressure
194  print *,"**************************************************************"
195 
196  print *,"**************************************************************"
197  print *,"jet pressure to ambient test section pressure"
198  print*,"PR_jet=",fuelpressure/testsectionpressure
199  print *,"**************************************************************"
200 
201  print *,"**************************************************************"
202  print *,"Reynolds number of the test section"
203  print*,"Re=0.008 * testSectionVel * testSectionRho/9.0865272E-6=",0.008*testsectionvelocity*testsectiondensity/9.0865272e-6
204  print *,"**************************************************************"
205 
206  print *,"**************************************************************"
207  print *,"Reynolds number of the jet exit"
208  print*,"Re=0.000195 * fueVel * fuelRho/7.7724307E-6=",0.000195*fuelvelocity*fueldensity/7.7724307e-6
209  print *,"**************************************************************"
210 
211  !9.0865272E-6
212 
213  !get location of executable
214  call get_command_argument(0, cmd)
215  execpath(1:len_trim(cmd))=cmd(1:len_trim(cmd))
216  !get command line arguments
217  allocate(rawarguments(command_argument_count()))
218  do i = 1, size(rawarguments)
219  call get_command_argument(i, rawarguments(i))
220  end do
221 
222  options(1) = t_cmd_opt_("format", "f", opt_value_type_string) !HDF5 or PLOT3D I/O
223  options(2) = t_cmd_opt_("nptsx", "i", opt_value_type_integer) !number of points in x direction
224  options(3) = t_cmd_opt_("nptsy", "j", opt_value_type_integer) !number of points in x direction
225  options(4) = t_cmd_opt_("ly", "H", opt_value_type_real) !height of domain
226  options(5) = t_cmd_opt_("lx", "W", opt_value_type_real) !width of domain
227  options(6) = t_cmd_opt_("plug radius ", "r", opt_value_type_real) !plug radius
228  options(7) = t_cmd_opt_("slot width ", "w", opt_value_type_real) !slotted jet width
229  options(8) = t_cmd_opt_("cross stream Mach", "M", opt_value_type_real) !slotted jet width
230  options(9) = t_cmd_opt_("dimensional or nondimensional", "D", opt_value_type_integer)!slotted jet width
231  options(10) = t_cmd_opt_("pressure ratio", "p",opt_value_type_real)!slotted jet width
232  options(11) = t_cmd_opt_("x", "x",opt_value_type_real)!slottedjet width
233  options(12) = t_cmd_opt_("y", "y",opt_value_type_real)!slottedjet width
234 
235 
236  call parsearguments(rawarguments, options=options)
237 
238  !I/O Stuff
239  if (options(1)%is_present) then
240  if (options(1)%value == "plot3d") then
241  outputformat = output_format_plot3d
242  else if (options(1)%value == "hdf5") then
243  outputformat = output_format_hdf5
244  else
245  write (error_unit, '(3a)') "ERROR: Unrecognized grid format '", trim(options(1)%value), "'."
246  stop 1
247  end if
248  else
249  outputformat = defaultoutputformat
250  end if
251 
252  if (options(2)%is_present) then
253  read (options(2)%value, *) nx
254  else
255  nx = 500*nrefine
256  end if
257 
258  if (options(3)%is_present) then
259  read (options(3)%value, *) ny
260  else
261  ny = 1000*nrefine
262  end if
263 
264  if (options(4)%is_present) then
265  read (options(4)%value, *) ly
266  else
267  ly = 56.0_rk*referencelength
268  end if
269 
270  if (options(5)%is_present) then
271  read (options(5)%value, *) lx
272  else
273  lx = 14.0_rk*referencelength
274  end if
275 
276  if (options(6)%is_present) then
277  read (options(6)%value, *) plugradius
278  else
279  plugradius = 4.0_rk*referencelength
280  end if
281 
282  if (options(7)%is_present) then
283  read (options(7)%value, *) slotwidth
284  else
285  slotwidth = 5.0_rk*referencelength
286  end if
287 
288  if (options(8)%is_present) then
289  read (options(8)%value, *) machcrossstream
290  else
291  machcrossstream = 0._rk
292  end if
293 
294  if (options(10)%is_present) then
295  read (options(10)%value, *) densityratio
296  else
297  densityratio=1.
298  end if
299 
300 !LIB POSITIONS RELATIVE TO THE JET
301 if (options(11)%is_present) then
302  read (options(11)%value, *) verticaloffsetfromjet
303  else
304  verticaloffsetfromjet=-4.00
305  end if
306 
307 if (options(12)%is_present) then
308  read (options(12)%value, *) horizontaloffsetfromcenterline
309  else
310  horizontaloffsetfromcenterline=7.43
311  end if
312 
313  !grid creation
314  npoints = [nx, ny]
315  length = [lx, ly]
316 
317  dx=length(1)/real(npoints(1)-1)
318  dy=length(2)/real(npoints(2)-1)
319 
320  allocate(x(2,npoints(1),npoints(2)))
321  allocate(ib(npoints(1),npoints(2)))
322  ib(:,:) = 1
323 
324  !simple uniform mesh stretching
325  do j = 1, npoints(2)
326  do i = 1, npoints(1)
327  xtilde = real(i-1, kind=rk)/real(npoints(1)-1, kind=rk)
328  ytilde = real(j-1, kind=rk)/real(npoints(2)-1, kind=rk)
329  u = xtilde
330  v = ytilde
331  x(:,i,j) = (length * [u,v])- [0.0_rk,0.0_rk]
332  end do
333  end do
334 
335  !allocate Q vars
336  allocate(q(4,npoints(1),npoints(2)))
337  allocate(qaux(nspecies,npoints(1),npoints(2)))
338  allocate(massfractions(nspecies,npoints(1),npoints(2)))
339  allocate(p(npoints(1),npoints(2)))
340  allocate(t(npoints(1),npoints(2)))
341 
342  !plug (i.e. the 'sting') radius is 4 mm
343  !start the jet exit at 5\times 4 mm
344  jslottedjetstart=int(5.0*plugradius/dy)
345  jslottedjetend=jslottedjetstart+int(slotwidth/dy)
346  print *,"Number of points across slot=",abs(jslottedjetstart-jslottedjetend)
347 
348  iplug=int(plugradius/dx)
349  ystartjet=x(2,iplug,jslottedjetstart)
350  yendjet=x(2,iplug,jslottedjetend)
351 
352  !iblank the plug
353  do j = 1, npoints(2)
354  do i = 1, iplug-1
355  ib(i,j)=0.
356  end do
357  end do
358 
359  jetstart=7*iplug/8
360  do j = jslottedjetstart,jslottedjetend
361  do i = jetstart, iplug
362  ib(i,j)=1.
363  end do
364  end do
365 
366  !copied directly from jet in cross flow initialization per model0 specification
367  in2 = nspecies + 1
368  allocate(mwcoeff(nspecies+1), mwcoeffinv(nspecies+1))
369  mwcoeff(ih2) = 2.0;
370  mwcoeff(io2) = 32.0;
371  if (nspecies>=3) mwcoeff(ih) = 1.0_rk
372  if (nspecies>=4) mwcoeff(ih2o) = 18.0_rk
373  if (nspecies>=5) mwcoeff(iho2) = 33.0_rk
374  if (nspecies>=6) mwcoeff(ih2o2) = 34.0_rk
375  if (nspecies>=7) mwcoeff(io) = 16.0_rk
376  if (nspecies>=8) mwcoeff(ioh) = 17.0_rk
377  mwcoeff(in2) = 28.0_rk
378  nitrogenoxygenmoleratio = 3.76_rk
379  yo2 = 1.0_rk/(1.0_rk+7.0_rk/8.0_rk*nitrogenoxygenmoleratio);
380  mwa = (mwcoeff(io2) + mwcoeff(in2)*nitrogenoxygenmoleratio)/(1.0_rk+nitrogenoxygenmoleratio)
381  rair = gasconstant / mwa
382  cref = sqrt(gamma*rair*tref)
383  cref = cref / machfactor
384  do i=1,nspecies+1
385  mwcoeff(i) = 1.0_rk / mwcoeff(i)
386  enddo
387  mwref = yo2*mwcoeff(io2) + (1.0_rk-yo2)*mwcoeff(in2)
388  mwcoeffrho=1.0_rk/mwcoeff(in2)/mwref
389  mwcoeff = mwcoeff/mwref
390  do i=1,nspecies
391  mwcoeff(i) = mwcoeff(i)-mwcoeff(in2)
392  enddo
393 
394  !some gut checks to make sure `luca code' makes physical sense
395  print *,"**************************************************************"
396  print *,"some gut checks to make sure `luca code' makes physical sense"
397  print *,"**************************************************************"
398  massfractions(:,:,:)=0.0_rk !pure nitrogen
399  massfractions(in2,:,:)=1.0_rk !pure nitrogen
400  print*,"density of nitrogen[kg/m^3]=",1.0_rk/(mwcoeff(in2)+sum(mwcoeff(1:nspecies)*massfractions(1:nspecies,1,1)))*nondimr
401  massfractions(:,:,:)=0.0_rk !pure nitrogen
402  massfractions(ih2,:,:)=1.0_rk !pure hydrogen
403  print*,"density of hydrogen[kg/m^3]=",1.0_rk/(mwcoeff(in2)+sum(mwcoeff(1:nspecies)*massfractions(1:nspecies,1,1)))*nondimr
404  massfractions(:,:,:)=0.0_rk
405  massfractions(io2,:,:)=yo2
406  massfractions(in2,:,:)=1.0-yo2
407  print *,"density of air[kg/m^3]=",1.0_rk/(mwcoeff(in2) +sum(mwcoeff(1:nspecies)*massfractions(1:nspecies,1,1)))*nondimr
408  print *,"**************************************************************"
409 
410  print *,"**************************************************************"
411  print *,"ad-hoc boundary layer of delta_99 = slot width"
412  print *,"The functional form=tanh(2.646652412/(slotwidth)*(xpos-*xplug))"
413  print *,"**************************************************************"
414  cref=1.0
415  massfractions(:,:,:)=0._rk
416  massfractions(io2,:,:)=1.0_rk !YO2
417  xplug=x(1,iplug,1)
418 
419  !density(l0)*temperature(l0) / gamma
420 
421  do i=1,npoints(1)
422  do j=1,npoints(2)
423 
424  if (i .ge. iplug) then
425  xpos=x(1,i,j)
426  q(1,i,j)=testsectiondensity/nondimr !1.0_rk/(Mwcoeff(iN2) + sum(Mwcoeff(1:nspecies)*massFractions(1:nspecies,i,j)))
427  q(3,i,j)=q(1,i,j)*testsectiondensity/nondimvel*tanh(2.646652412/(slotwidth)*(xpos-xplug))
428  q(4,i,j)=q(1,i,j)*testsectiontemperature/nondimt/gamma + 0.5_rk * q(3,i,j)**2/q(1,i,j)
429  qaux(1:nspecies,i,j)=q(1,i,j) * massfractions(1:nspecies,i,j)
430  else
431  q(1,i,j)=testsectiondensity/nondimr !1.0_rk/(Mwcoeff(iN2) + sum(Mwcoeff(1:nspecies)*massFractions(1:nspecies,i,j)))
432  q(2,i,j)=0.
433  q(3,i,j)=0.
434  q(4,i,j)=q(1,i,j)*testsectiontemperature/nondimt/gamma + 0.5_rk * q(3,i,j)**2/q(1,i,j)
435  qaux(1:nspecies,i,j)=q(1,i,j) * massfractions(1:nspecies,i,j)
436  end if
437 
438  end do
439  end do
440 
441 
442 !This adds in the LIB on top of the provided Q solution
443 if (.false.) then
444 
445  !read grid from example directory
446  !GridPath = trim(ExecPath)//trim(TemplateFlnm)
447  ssprec = ""; ssgf = ""; ssvf = ""; ssiblocal = ""
448  print *,"made it here"
449  print *,"sizeof(SSND)",sizeof(ssnd)
450  allocate(ssnd(1,3))
451  print *,ssnd
452  deallocate(ssnd)
453  print *,"going to read the mesh"
454  gridpath=trim("grid.xyz")
455  solpath=trim("solution.q")
456  call read_grid_size(ssndim, ssngrid, ssnd, gridpath, 1, ssiblocal)
457  Call read_grid(ssndim, ssngrid, ssnd, xtemp, ssib,ssprec,ssgf,ssvf,ssiblocal,gridpath, 1)
458  print*,'SS grid X extent is',minval(xtemp(:,:,:,:,1)),maxval(xtemp(:,:,:,:,1))
459  print*,'SS grid Y extent is',minval(xtemp(:,:,:,:,2)),maxval(xtemp(:,:,:,:,2))
460  Call read_soln_header(ssndim, ssngrid, ssnd,solpath, sstau)
461  print*,'Read soln, size is', ssndim,ssngrid,ssnd,sstau
462  Call read_soln(ssndim, ssngrid, ssnd, qtemp, sstau, ssprec, ssgf, ssvf,solpath, 1)
463  print*,'Read soln, size is', shape(qtemp)
464 
465  do j=1,npoints(2)
466  do i=1,npoints(1)
467  q(1,i,j) = qtemp(1,i,j,1,1)
468  q(2,i,j) = qtemp(1,i,j,1,2)
469  q(3,i,j) = qtemp(1,i,j,1,3)
470  q(4,i,j) = qtemp(1,i,j,1,5)
471  end do
472  end do
473 
474  jslotjetcenter=int((jslottedjetstart+jslottedjetend)/2)
475  verticaloffsetfromjet=verticaloffsetfromjet+xtemp(1,1,jslotjetcenter,1,2)
476  iplacelib=0
477  jplacelib=0
478  do j=1,npoints(2)
479  do i=1,npoints(1)
480  if (xtemp(1,i,j,1,1).le.horizontaloffsetfromcenterline) iplacelib=i
481  if (xtemp(1,i,j,1,2).le.verticaloffsetfromjet)jplacelib=j
482  end do
483  end do
484 
485  print *,"i,j of LIB",iplacelib,jplacelib
486  print*,xtemp(1,iplacelib,jplacelib,1,1),xtemp(1,iplacelib,jplacelib,1,2)-xtemp(1,iplacelib,jslotjetcenter,1,2)
487 
488  massfractions(:,:,:)=0.
489  filename='128x128.dat'
490  print *,"Reading lib data file: ",trim(filename)
491  nskip=18
492  OPEN(1,file=trim(filename))
493  do s=1,nskip
494  READ(1,*) dummyline
495  end do
496  do j=jplacelib-64,jplacelib+63
497  do i=iplacelib-64,iplacelib+63
498  xpos=x(1,i,j)
499  read(1,*),dummyval,dummyval,dummyval,&
500  dummyval,& !Qaux(7,i,j),&
501  dummyval,& !Qaux(2,i,j),&
502  uvellib,&! Q(2,i,j),&
503  vvellib,&!Q(3,i,j),&
504  dummyval,& !ignore the w-velocity
505  temperaturelib,& !Q(4,i,j),&
506  densitylib,& !Q(1,i,j)
507  yolib,&
508  yo2lib
509 
510  if (temperaturelib .ge. 300.) then
511 
512  yo2libref=0.232917502522468567
513  densitylibref=1.22
514  temperaturelibref=288.
515  velocitylibref=343.
516 
517  q(4,i,j)=1.89*temperaturelib/temperaturelibref*tref/gamma*q(1,i,j) + 0.5_rk *q(3,i,j)**2/q(1,i,j)+ 0.5_rk * q(2,i,j)**2/q(1,i,j)
518 
519  end if
520  end do
521  end do
522  close(1)
523 
524 end if
525 
526  call writeplot3dsolution("initial.q", ndims=2, npoints=npoints, q=q)
527  call writeplot3dfunc("initial.aux.q", ndims=2, npoints=npoints, f=qaux)
528 
529  !initializing the target data for the sonic hydrogen jet
530  !underexapnded with the pressure from the input deck
531  massfractions(:,:,:)=0._rk
532  massfractions(ih2,:,:)=1.0_rk
533  do j=jslottedjetstart,jslottedjetend
534  do i=jetstart,iplug
535  y=x(2,i,j)
536  xpos=x(1,i,j)
537  q(1,i,j)=fueldensity/nondimr !DensityRatio/(Mwcoeff(iN2) +sum(Mwcoeff(1:nspecies)*massFractions(1:nspecies,i,j)))
538  q(2,i,j)=q(1,i,j)*fuelvelocity/nondimvel!*(tanh(10.*(y-ystartjet))-tanh(10.*(y-yendJet))-1.)
539  q(3,i,j)=0._rk
540  q(4,i,j)=q(1,i,j)*fueltemperature/nondimt/gamma+0.5*(q(2,i,j)**2)/q(1,i,j)
541  qaux(1:nspecies,i,j)=q(1,i,j)*massfractions(1:nspecies,i,j)
542  end do
543  end do
544 
545  call writeplot3dsolution("initial.target.q", ndims=2, npoints=npoints, q=q)
546  call writeplot3dfunc("initial.target.aux.q", ndims=2, npoints=npoints, f=qaux)
547 
548  print *,"**************************************************************"
549  print *,"The ambient pressure to jet pressure ratio="!,!P
550  print *,"**************************************************************"
551 
552  allocate(bcs(11))
553  bcs(1) = t_bc_(1, bc_type_sat_slip_adiabatic_wall, -1, [-1,-1], [1,-1])
554  bcs(2) = t_bc_(1, bc_type_sat_far_field, 2, [iplug,-1], [1,1])
555  bcs(3) = t_bc_(1, bc_type_sat_far_field, -2, [iplug,-1], [-1,-1])
556  bcs(4) = t_bc_(1, bc_type_sat_slip_adiabatic_wall,1,[iplug,iplug],[1,jslottedjetstart])
557  bcs(5) = t_bc_(1, bc_type_sat_slip_adiabatic_wall,1,[iplug,iplug],[jslottedjetend,-1])
558  bcs(6) = t_bc_(1, bc_type_sponge, -2, [iplug,-1],[npoints(2)-int(plugradius/dy),-1])
559  bcs(7) = t_bc_(1, bc_type_sponge, 2, [iplug,-1], [1,int(plugradius/dy)])
560  bcs(8) = t_bc_(1, bc_type_sat_far_field,1,[jetstart,jetstart],[jslottedjetstart,jslottedjetend])
561  bcs(9) = t_bc_(1, bc_type_sat_slip_adiabatic_wall,2,[jetstart,iplug],[jslottedjetstart,jslottedjetstart])
562  bcs(10) = t_bc_(1, bc_type_sat_slip_adiabatic_wall,-2,[jetstart,iplug],[jslottedjetend,jslottedjetend])
563  bcs(11) = t_bc_(1, bc_type_sponge, 1,[jetstart,iplug],[jslottedjetstart,jslottedjetend])
564 
565  call writeplot3dgrid("grid.xyz", ndims=2, npoints=npoints, x=x, iblank = ib)
566  call writebcs(bcs, "bc.dat")
567 
568 contains
569 
570 !consider having total (stagnation properties as inputs)
571 real function get_isentropic_pressure(M,Po,gamma)
572 real(rk)::m
573 real(rk)::Po
574 real(rk)::gamma
576 get_isentropic_pressure=(1.+(gamma-1.)/2.*m**2)**(-gamma/(gamma-1.))*po
577 end function
578 real function get_isentropic_density(M,rhoo,gamma)
579 real(rk)::M
580 real(rk)::rhoo
581 real(rk)::gamma
583 get_isentropic_density=(1.+(gamma-1.)/2.*m**2)**(-1./(gamma-1.))*rhoo
584 end function
585 real function get_isentropic_temperature(M,To,gamma)
586 real(rk)::M
587 real(rk)::To
588 real(rk)::gamma
590 get_isentropic_temperature=(1.+(gamma-1.)/2.*m**2)**(-1)*to
591 end function
592 real function get_isentropic_soundspeed(M,co,gamma)
593 real(rk)::M
594 real(rk)::co
595 real(rk)::gamma
597 get_isentropic_soundspeed=(1.+(gamma-1.)/2.*m**2)**(-1./2.)*co
598 end function
599 
600 end program impingingjetaxisym
601 
602 Subroutine p3d_read_soln_header(NDIM, ngrid, ND, fname, tau)
604  ! ... function call variables
605  Integer :: NDIM, ngrid
606  Integer, Dimension(:,:), Pointer :: ND
607  Character(LEN=*) :: fname
608  Real(KIND=8) :: tau(4)
609 
610  ! ... local variables
611  Integer :: ibuf, I, J
612 
613  ! ... open the file
614  Open (unit=10, file=trim(fname), form='unformatted', status='old')
615 
616  ! ... read the number of grids, exit if error
617  Read (10) ibuf
618  print *,ibuf
619 
620  ! ... read the size of each grid, throw value away
621  Read (10) ((ibuf,j=1,ndim),i=1,ngrid)
622  print *,ndim
623 
624  ! ... read the header
625  Read (10) tau
626  print *,tau
627 
628  ! ... close and exit
629  Close (10)
630 
631  End Subroutine p3d_read_soln_header
632 
633  Subroutine p3d_read_soln(NDIM, ngrid, ND, X, tau, prec, gf, vf, file, OF)
635  Implicit None
636 
637  Real(KIND=8), Dimension(:,:,:,:,:), Pointer :: X
638  Real(KIND=8) :: tau(4)
639  Character(LEN=2) :: prec, gf, vf, ib
640  Character(LEN=80) :: file
641  Integer :: ngrid, I, J, K, L, M, Nx, Ny, Nz, NDIM, ftype
642  Integer, Dimension(:,:), Pointer :: ND
643  Real(KIND=4), Dimension(:,:,:,:), Pointer :: fX
644  Real(KIND=4) :: ftau(4)
645  Logical :: gf_exists
646  Integer :: OF
647 
648  Inquire(file=trim(file),exist=gf_exists)
649  If (.NOT.gf_exists) Then
650  Write (*,'(A,A,A)') 'File ', file(1:len_trim(file)), ' is not readable'
651  stop
652  End If
653 
654  prec = ""; gf = ""; vf = ""; ib = ""
655  Call p3d_detect(len(trim(file)),trim(file),prec,ndim,gf,vf,ib,ftype)
656 
657  Open (unit=10, file=trim(file), form='unformatted', status='old')
658 
659  ! Read number of grids
660  If (gf(1:1) .eq. 's') Then
661  ngrid = 1
662  Else
663  Read (10) ngrid
664  End If
665 
666 
667  ! Read grid sizes
668  Allocate(nd(ngrid,3))
669  nd(:,3) = 1
670  Read (10) ((nd(i,j),j=1,ndim),i=1,ngrid)
671 
672  ! Allocate soln memory
673  nx = maxval(nd(:,1))
674  ny = maxval(nd(:,2))
675  If (ndim .EQ. 3) Then
676  nz = maxval(nd(:,3))
677  Else
678  nz = 1
679  End If
680  If (associated(x)) deallocate(x)
681  Allocate(x(ngrid,nx,ny,nz,ndim+2))
682  If (prec(1:1) .eq. 's') Allocate(fx(nx,ny,nz,ndim+2))
683  x = 0d0
684 
685  ! Read soln values
686  If (vf(1:1) .eq. 'w') Then
687  If (prec(1:1) .eq. 'd') Then
688  Do l = 1, ngrid
689  Read (10) tau(1), tau(2), tau(3), tau(4)
690  Read (10)((((x(l,i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim+2)
691  End Do
692  Else
693  Do l = 1, ngrid
694  Read (10) ftau(1), ftau(2), ftau(3), ftau(4)
695  Read (10)((((fx(i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim+2)
696  x(l,:,:,:,:) = dble(fx(:,:,:,:))
697  tau = dble(ftau)
698  End Do
699  End If
700 
701  Else
702  If (prec(1:1) .eq. 'd') Then
703  Do l = 1, ngrid
704  Read (10) tau(1), tau(2), tau(3), tau(4)
705  Do k = 1, nd(l,3)
706  Read (10) (((x(l,i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),m=1,ndim+2)
707  End Do
708  End Do
709  Else
710  Do l = 1, ngrid
711  Read (10) ftau(1), ftau(2), ftau(3), ftau(4)
712  Do k = 1, nd(l,3)
713  Read (10) (((fx(i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),m=1,ndim+2)
714  End Do
715  x(l,:,:,:,:) = dble(fx(:,:,:,:))
716  tau = dble(ftau)
717  End Do
718  End If
719  End If
720 
721  Close (10)
722 
723  If (prec(1:1) .eq. 's') Deallocate(fx)
724 
725  Return
726  End Subroutine p3d_read_soln
727 
728  Subroutine p3d_read_grid(NDIM, ngrid, ND, X, IBLANK, prec, gf, vf, ib, file,OF)
730  Implicit None
731 
732  Real(KIND=8), Dimension(:,:,:,:,:), Pointer :: X
733  Integer, Dimension(:,:,:,:), Pointer :: IBLANK
734  Character(LEN=2) :: prec, gf, vf, ib
735  Character(LEN=80) :: file
736  Integer :: ngrid, I, J, K, L, Nx, Ny, Nz, NDIM, M, ftype
737  Integer, Dimension(:,:), Pointer :: ND
738  Integer :: OMap(3), NMap(3), ND_copy(3)
739  Real(KIND=4), Dimension(:,:,:,:), Pointer :: fX
740  Logical :: gf_exists
741  Integer :: OF
742 
743  Inquire(file=trim(file),exist=gf_exists)
744  If (.NOT.gf_exists) Then
745  Write (*,'(A,A,A)') 'File ', file(1:len_trim(file)), ' is not readable'
746  stop
747  End If
748 
749  prec = ""; gf = ""; vf = ""; ib = ""
750  Call p3d_detect(len(trim(file)),trim(file),prec,ndim,gf,vf,ib,ftype)
751 
752  Open (unit=10, file=trim(file), form='unformatted', status='old')
753 
754  ! Read number of grids
755  If (gf(1:1) .eq. 's') Then
756  ngrid = 1
757  Else
758  Read (10) ngrid
759  End If
760  Allocate(nd(ngrid,3))
761 
762  ! Read grid sizes
763  nd(:,3) = 1
764  Read (10) ((nd(i,j),j=1,ndim),i=1,ngrid)
765 
766  ! Allocate grid memory
767  nx = maxval(nd(:,1))
768  ny = maxval(nd(:,2))
769  nz = maxval(nd(:,3))
770  Allocate(x(ngrid,nx,ny,nz,ndim))
771  If (prec(1:1) .eq. 's') Allocate(fx(nx,ny,nz,ndim))
772  Allocate(iblank(ngrid,nx,ny,nz))
773 
774  ! Read grid values
775  If (vf(1:1) .eq. 'w') Then
776  If (prec(1:1) .eq. 'd') Then
777  If (ib(1:1) .eq. 'n') Then
778  Do l = 1, ngrid
779  Read (10)((((x(l,i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim)
780  End Do
781  Else
782  Do l = 1, ngrid
783  Read (10)((((x(l,i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim), &
784  (((iblank(l,i,j,k),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3))
785  End Do
786  End If
787  Else
788  If (ib(1:1) .eq. 'n') Then
789  Do l = 1, ngrid
790  Read (10)((((fx(i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim)
791  x(l,:,:,:,:) = dble(fx(:,:,:,:))
792  End Do
793  Else
794  Do l = 1, ngrid
795  Read (10)((((fx(i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3)),m=1,ndim), &
796  (((iblank(l,i,j,k),i=1,nd(l,1)),j=1,nd(l,2)),k=1,nd(l,3))
797  x(l,:,:,:,:) = dble(fx(:,:,:,:))
798  End Do
799  End If
800  End If
801 
802  Else
803  If (ndim .EQ. 3) Then
804  If (prec(1:1) .eq. 'd') Then
805  If (ib(1:1) .eq. 'n') Then
806  Do l = 1, ngrid
807  Do k = 1, nd(l,3)
808  Read (10) ((x(l,i,j,k,1),i=1,nd(l,1)),j=1,nd(l,2)), &
809  ((x(l,i,j,k,2),i=1,nd(l,1)),j=1,nd(l,2)), &
810  ((x(l,i,j,k,3),i=1,nd(l,1)),j=1,nd(l,2))
811  End Do
812  End Do
813  Else
814  Do l = 1, ngrid
815  Do k = 1, nd(l,3)
816  Read (10) ((x(l,i,j,k,1),i=1,nd(l,1)),j=1,nd(l,2)), &
817  ((x(l,i,j,k,2),i=1,nd(l,1)),j=1,nd(l,2)), &
818  ((x(l,i,j,k,3),i=1,nd(l,1)),j=1,nd(l,2)), &
819  ((iblank(l,i,j,k),i=1,nd(l,1)),j=1,nd(l,2))
820  End Do
821  End Do
822  End If
823  Else
824  If (ib(1:1) .eq. 'n') Then
825  Do l = 1, ngrid
826  Do k = 1, nd(l,3)
827  Read (10) ((fx(i,j,k,1),i=1,nd(l,1)),j=1,nd(l,2)), &
828  ((fx(i,j,k,2),i=1,nd(l,1)),j=1,nd(l,2)), &
829  ((fx(i,j,k,3),i=1,nd(l,1)),j=1,nd(l,2))
830  End Do
831  x(l,:,:,:,:) = dble(fx(:,:,:,:))
832  End Do
833  Else
834  Do l = 1, ngrid
835  Do k = 1, nd(l,3)
836  Read (10) ((fx(i,j,k,1),i=1,nd(l,1)),j=1,nd(l,2)), &
837  ((fx(i,j,k,2),i=1,nd(l,1)),j=1,nd(l,2)), &
838  ((fx(i,j,k,3),i=1,nd(l,1)),j=1,nd(l,2)), &
839  ((iblank(l,i,j,k),i=1,nd(l,1)),j=1,nd(l,2))
840  End Do
841  x(l,:,:,:,:) = dble(fx(:,:,:,:))
842  End Do
843  End If
844  End If
845  Else
846  If (prec(1:1) .eq. 'd') Then
847  If (ib(1:1) .eq. 'n') Then
848  Do l = 1, ngrid
849  Do j = 1, nd(l,2)
850  Read (10) (x(l,i,j,1,1),i=1,nd(l,1)), &
851  (x(l,i,j,1,2),i=1,nd(l,1))
852  End Do
853  End Do
854  Else
855  Do l = 1, ngrid
856  Do j = 1, nd(l,2)
857  Read (10) (x(l,i,j,1,1),i=1,nd(l,1)), &
858  (x(l,i,j,1,2),i=1,nd(l,1)), &
859  (iblank(l,i,j,1),i=1,nd(l,1))
860  End Do
861  End Do
862  End If
863  Else
864  If (ib(1:1) .eq. 'n') Then
865  Do l = 1, ngrid
866  Do k = j, nd(l,2)
867  Read (10) (fx(i,j,1,1),i=1,nd(l,1)), &
868  (fx(i,j,1,2),i=1,nd(l,1))
869  End Do
870  x(l,:,:,:,:) = dble(fx(:,:,:,:))
871  End Do
872  Else
873  Do l = 1, ngrid
874  Do k = j, nd(l,2)
875  Read (10) (fx(i,j,1,1),i=1,nd(l,1)), &
876  (fx(i,j,1,2),i=1,nd(l,1)), &
877  (iblank(l,i,j,1),i=1,nd(l,1))
878  End Do
879  x(l,:,:,:,:) = dble(fx(:,:,:,:))
880  End Do
881  End If
882  End If
883  End If
884  End If
885 
886  Close (10)
887 
888  If (prec(1:1) .eq. 's') Deallocate(fx)
889  If (ib(1:1) .eq. 'n') iblank = 1
890 
891  Return
892  End Subroutine p3d_read_grid
893 
894 
subroutine p3d_read_soln(NDIM, ngrid, ND, X, tau, prec, gf, vf, file, OF)
Definition: InitialY4.f90:634
real function get_isentropic_temperature(M, To, gamma)
Definition: InitialY4.f90:586
real function get_isentropic_density(M, rhoo, gamma)
Definition: InitialY4.f90:579
real function get_isentropic_pressure(M, Po, gamma)
Definition: InitialY4.f90:572
real function get_isentropic_soundspeed(M, co, gamma)
Definition: InitialY4.f90:593
program impingingjetaxisym
Definition: InitialY4.f90:1
subroutine p3d_read_soln_header(NDIM, ngrid, ND, fname, tau)
Definition: InitialY4.f90:603
subroutine p3d_read_grid(NDIM, ngrid, ND, X, IBLANK, prec, gf, vf, ib, file, OF)
Definition: InitialY4.f90:729