10 integer(ik) :: i, j, k
11 character(len=CMD_ARG_LENGTH),
dimension(:),
allocatable :: RawArguments
12 type(t_cmd_opt),
dimension(12) :: Options
14 integer(ik) :: OutputFormat
16 real(rk),
dimension(:,:),
allocatable :: xfac, yfac
17 integer(ik) :: i1, j1, k1, i2, j2, k2, IBcheck
19 character(120) :: ExecPath,GridPath,SolPath
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
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
35 real(rk) :: Density, DensInv, Lref
37 real(rk),
dimension(2) :: Velocity
38 integer(ik),
dimension(2) :: nSponge
39 real(rk),
dimension(:),
allocatable :: Mwcoeff, MwcoeffInv
40 Integer (ik) :: VolRateSpecified = 0
42 integer(ik)::useDimensional
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
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
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
68 real(rk)::ystartJet,yendJet,ymid,y
69 integer(ik),
parameter::Nrefine=1
70 real(rk),
parameter::ReferenceLength=1.0
72 integer(ik),
parameter::depthSlottedJet=20
84 real(rk)::machCrossStream
86 real(rk)::Tref,rhoref,cref,rhoYO2Ref,rhoH2ref,DensityRatio
88 character(len=1000)::filename,dummyline
90 logical::AIR_INTO_AIR, HYDROGEN_INTO_AIR
94 real(rk)::tmp,tmp2,pressure,temperature
97 real(rk)::densityLIBREF,temperatureLIBREF,velocityLIBREF
98 real(rk)::densityLIB,vvelLIB,uvelLIB,temperatureLIB,YOLIB,YO2LIB,YO2LIBREF
100 integer :: SSptsX, SSptsY, SSNdim, SSngrid, SSftype, SSNvar
101 Character(LEN=2) :: SSprec, SSgf, SSvf, SSiblocal
103 integer,
pointer,
dimension(:,:) :: SSND
104 integer,
allocatable,
dimension(:,:) :: ND
108 real(rk):: MachNumberPreShock
109 real(rk):: DensityPreShock
110 real(rk):: TemperaturePreShock
111 real(rk):: SoundSpeedPreShock
113 real(rk):: MachNumberPostShock
114 real(rk):: DensityPostShock
115 real(rk):: TemperaturePostShock
116 real(rk):: SoundSpeedPostShock
118 real(rk)::VerticalOffSetFromJet
119 real(rk)::HorizontalOffSetFromCenterline
120 integer::jSlotJetCenter,iPlaceLIB,jPlaceLIB
123 real(rk),
parameter::airPoGS=167.1_rk*1.e3
124 real(rk),
parameter::airToGs=298.0_rk
125 real(rk),
parameter::fuelPoGS=386.6_rk*1.e3
126 real(rk),
parameter::fuelToGS=298.0_rk
127 real(rk),
parameter::airMdotGS=56.38_rk
128 real(rk),
parameter::fuelMdotGS=1.842_rk
129 real(rk)::airRoGS,fuelRoGs,airCoGS,fuelCoGs
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
136 real(rk),
parameter::nondimT=298.*(gamma-1.0)
137 real(rk),
parameter::nondimP=101.325
138 real(rk),
parameter::nondimR=1.2041
139 real(rk),
parameter::nondimVel=343.
141 airrogs = airpogs / airtogs / 259.8
142 fuelrogs = fuelpogs / fueltogs / 4124.
143 aircogs = sqrt(gamma * airpogs / airrogs)
144 fuelcogs = sqrt(gamma * fuelpogs / fuelrogs)
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 *,
"**************************************************************" 160 testsectionvelocity=testsectionmachnumber*testsectionsoundspeed
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 *,
"**************************************************************" 175 fuelvelocity=fuelmachnumber*fuelsoundspeed
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 *,
"**************************************************************" 186 print *,
"**************************************************************" 187 print *,
"Momentum Ratio of Test Section to Jet" 188 print*,
"J=",fueldensity*fuelvelocity**2/testsectiondensity/testsectionvelocity**2
189 print *,
"**************************************************************" 191 print *,
"**************************************************************" 192 print *,
"Stagnation jet pressure to ambient test section pressure" 193 print*,
"PR=",fuelpogs/testsectionpressure
194 print *,
"**************************************************************" 196 print *,
"**************************************************************" 197 print *,
"jet pressure to ambient test section pressure" 198 print*,
"PR_jet=",fuelpressure/testsectionpressure
199 print *,
"**************************************************************" 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 *,
"**************************************************************" 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 *,
"**************************************************************" 214 call get_command_argument(0, cmd)
215 execpath(1:len_trim(cmd))=cmd(1:len_trim(cmd))
217 allocate(rawarguments(command_argument_count()))
218 do i = 1,
size(rawarguments)
219 call get_command_argument(i, rawarguments(i))
222 options(1) = t_cmd_opt_(
"format",
"f", opt_value_type_string)
223 options(2) = t_cmd_opt_(
"nptsx",
"i", opt_value_type_integer)
224 options(3) = t_cmd_opt_(
"nptsy",
"j", opt_value_type_integer)
225 options(4) = t_cmd_opt_(
"ly",
"H", opt_value_type_real)
226 options(5) = t_cmd_opt_(
"lx",
"W", opt_value_type_real)
227 options(6) = t_cmd_opt_(
"plug radius ",
"r", opt_value_type_real)
228 options(7) = t_cmd_opt_(
"slot width ",
"w", opt_value_type_real)
229 options(8) = t_cmd_opt_(
"cross stream Mach",
"M", opt_value_type_real)
230 options(9) = t_cmd_opt_(
"dimensional or nondimensional",
"D", opt_value_type_integer)
231 options(10) = t_cmd_opt_(
"pressure ratio",
"p",opt_value_type_real)
232 options(11) = t_cmd_opt_(
"x",
"x",opt_value_type_real)
233 options(12) = t_cmd_opt_(
"y",
"y",opt_value_type_real)
236 call parsearguments(rawarguments, options=options)
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
245 write (error_unit,
'(3a)')
"ERROR: Unrecognized grid format '", trim(options(1)%value),
"'." 249 outputformat = defaultoutputformat
252 if (options(2)%is_present)
then 253 read (options(2)%value, *) nx
258 if (options(3)%is_present)
then 259 read (options(3)%value, *) ny
264 if (options(4)%is_present)
then 265 read (options(4)%value, *) ly
267 ly = 56.0_rk*referencelength
270 if (options(5)%is_present)
then 271 read (options(5)%value, *) lx
273 lx = 14.0_rk*referencelength
276 if (options(6)%is_present)
then 277 read (options(6)%value, *) plugradius
279 plugradius = 4.0_rk*referencelength
282 if (options(7)%is_present)
then 283 read (options(7)%value, *) slotwidth
285 slotwidth = 5.0_rk*referencelength
288 if (options(8)%is_present)
then 289 read (options(8)%value, *) machcrossstream
291 machcrossstream = 0._rk
294 if (options(10)%is_present)
then 295 read (options(10)%value, *) densityratio
301 if (options(11)%is_present)
then 302 read (options(11)%value, *) verticaloffsetfromjet
304 verticaloffsetfromjet=-4.00
307 if (options(12)%is_present)
then 308 read (options(12)%value, *) horizontaloffsetfromcenterline
310 horizontaloffsetfromcenterline=7.43
317 dx=length(1)/
real(npoints(1)-1)
318 dy=length(2)/
real(npoints(2)-1)
320 allocate(x(2,npoints(1),npoints(2)))
321 allocate(ib(npoints(1),npoints(2)))
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)
331 x(:,i,j) = (length * [u,v])- [0.0_rk,0.0_rk]
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)))
344 jslottedjetstart=int(5.0*plugradius/dy)
345 jslottedjetend=jslottedjetstart+int(slotwidth/dy)
346 print *,
"Number of points across slot=",abs(jslottedjetstart-jslottedjetend)
348 iplug=int(plugradius/dx)
349 ystartjet=x(2,iplug,jslottedjetstart)
350 yendjet=x(2,iplug,jslottedjetend)
360 do j = jslottedjetstart,jslottedjetend
361 do i = jetstart, iplug
368 allocate(mwcoeff(nspecies+1), mwcoeffinv(nspecies+1))
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
385 mwcoeff(i) = 1.0_rk / mwcoeff(i)
387 mwref = yo2*mwcoeff(io2) + (1.0_rk-yo2)*mwcoeff(in2)
388 mwcoeffrho=1.0_rk/mwcoeff(in2)/mwref
389 mwcoeff = mwcoeff/mwref
391 mwcoeff(i) = mwcoeff(i)-mwcoeff(in2)
395 print *,
"**************************************************************" 396 print *,
"some gut checks to make sure `luca code' makes physical sense" 397 print *,
"**************************************************************" 398 massfractions(:,:,:)=0.0_rk
399 massfractions(in2,:,:)=1.0_rk
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
402 massfractions(ih2,:,:)=1.0_rk
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 *,
"**************************************************************" 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 *,
"**************************************************************" 415 massfractions(:,:,:)=0._rk
416 massfractions(io2,:,:)=1.0_rk
424 if (i .ge. iplug)
then 426 q(1,i,j)=testsectiondensity/nondimr
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)
431 q(1,i,j)=testsectiondensity/nondimr
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)
447 ssprec =
""; ssgf =
""; ssvf =
""; ssiblocal =
"" 448 print *,
"made it here" 449 print *,
"sizeof(SSND)",sizeof(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)
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)
474 jslotjetcenter=int((jslottedjetstart+jslottedjetend)/2)
475 verticaloffsetfromjet=verticaloffsetfromjet+xtemp(1,1,jslotjetcenter,1,2)
480 if (xtemp(1,i,j,1,1).le.horizontaloffsetfromcenterline) iplacelib=i
481 if (xtemp(1,i,j,1,2).le.verticaloffsetfromjet)jplacelib=j
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)
488 massfractions(:,:,:)=0.
489 filename=
'128x128.dat' 490 print *,
"Reading lib data file: ",trim(filename)
492 OPEN(1,file=trim(filename))
496 do j=jplacelib-64,jplacelib+63
497 do i=iplacelib-64,iplacelib+63
499 read(1,*),dummyval,dummyval,dummyval,&
510 if (temperaturelib .ge. 300.)
then 512 yo2libref=0.232917502522468567
514 temperaturelibref=288.
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)
526 call writeplot3dsolution(
"initial.q", ndims=2, npoints=npoints, q=q)
527 call writeplot3dfunc(
"initial.aux.q", ndims=2, npoints=npoints, f=qaux)
531 massfractions(:,:,:)=0._rk
532 massfractions(ih2,:,:)=1.0_rk
533 do j=jslottedjetstart,jslottedjetend
537 q(1,i,j)=fueldensity/nondimr
538 q(2,i,j)=q(1,i,j)*fuelvelocity/nondimvel
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)
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)
548 print *,
"**************************************************************" 549 print *,
"The ambient pressure to jet pressure ratio=" 550 print *,
"**************************************************************" 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])
565 call writeplot3dgrid(
"grid.xyz", ndims=2, npoints=npoints, x=x, iblank = ib)
566 call writebcs(bcs,
"bc.dat")
605 Integer :: NDIM, ngrid
606 Integer,
Dimension(:,:),
Pointer :: ND
607 Character(LEN=*) :: fname
608 Real(KIND=8) :: tau(4)
611 Integer :: ibuf, I, J
614 Open (unit=10, file=trim(fname), form=
'unformatted', status=
'old')
621 Read (10) ((ibuf,j=1,ndim),i=1,ngrid)
633 Subroutine p3d_read_soln(NDIM, ngrid, ND, X, tau, prec, gf, vf, file, OF)
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)
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' 654 prec =
""; gf =
""; vf =
""; ib =
"" 655 Call p3d_detect(len(trim(file)),trim(file),prec,ndim,gf,vf,ib,ftype)
657 Open (unit=10, file=trim(file), form=
'unformatted', status=
'old')
660 If (gf(1:1) .eq.
's')
Then 668 Allocate(nd(ngrid,3))
670 Read (10) ((nd(i,j),j=1,ndim),i=1,ngrid)
675 If (ndim .EQ. 3)
Then 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))
686 If (vf(1:1) .eq.
'w')
Then 687 If (prec(1:1) .eq.
'd')
Then 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)
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(:,:,:,:))
702 If (prec(1:1) .eq.
'd')
Then 704 Read (10) tau(1), tau(2), tau(3), tau(4)
706 Read (10) (((x(l,i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),m=1,ndim+2)
711 Read (10) ftau(1), ftau(2), ftau(3), ftau(4)
713 Read (10) (((fx(i,j,k,m),i=1,nd(l,1)),j=1,nd(l,2)),m=1,ndim+2)
715 x(l,:,:,:,:) = dble(fx(:,:,:,:))
723 If (prec(1:1) .eq.
's')
Deallocate(fx)
728 Subroutine p3d_read_grid(NDIM, ngrid, ND, X, IBLANK, prec, gf, vf, ib, file,OF)
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
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' 749 prec =
""; gf =
""; vf =
""; ib =
"" 750 Call p3d_detect(len(trim(file)),trim(file),prec,ndim,gf,vf,ib,ftype)
752 Open (unit=10, file=trim(file), form=
'unformatted', status=
'old')
755 If (gf(1:1) .eq.
's')
Then 760 Allocate(nd(ngrid,3))
764 Read (10) ((nd(i,j),j=1,ndim),i=1,ngrid)
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))
775 If (vf(1:1) .eq.
'w')
Then 776 If (prec(1:1) .eq.
'd')
Then 777 If (ib(1:1) .eq.
'n')
Then 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)
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))
788 If (ib(1:1) .eq.
'n')
Then 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(:,:,:,:))
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(:,:,:,:))
803 If (ndim .EQ. 3)
Then 804 If (prec(1:1) .eq.
'd')
Then 805 If (ib(1:1) .eq.
'n')
Then 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))
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))
824 If (ib(1:1) .eq.
'n')
Then 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))
831 x(l,:,:,:,:) = dble(fx(:,:,:,:))
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))
841 x(l,:,:,:,:) = dble(fx(:,:,:,:))
846 If (prec(1:1) .eq.
'd')
Then 847 If (ib(1:1) .eq.
'n')
Then 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))
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))
864 If (ib(1:1) .eq.
'n')
Then 867 Read (10) (fx(i,j,1,1),i=1,nd(l,1)), &
868 (fx(i,j,1,2),i=1,nd(l,1))
870 x(l,:,:,:,:) = dble(fx(:,:,:,:))
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))
879 x(l,:,:,:,:) = dble(fx(:,:,:,:))
888 If (prec(1:1) .eq.
's')
Deallocate(fx)
889 If (ib(1:1) .eq.
'n') iblank = 1
subroutine p3d_read_soln(NDIM, ngrid, ND, X, tau, prec, gf, vf, file, OF)
real function get_isentropic_temperature(M, To, gamma)
real function get_isentropic_density(M, rhoo, gamma)
real function get_isentropic_pressure(M, Po, gamma)
real function get_isentropic_soundspeed(M, co, gamma)
program impingingjetaxisym
subroutine p3d_read_soln_header(NDIM, ngrid, ND, fname, tau)
subroutine p3d_read_grid(NDIM, ngrid, ND, X, IBLANK, prec, gf, vf, ib, file, OF)