!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!
program blayer
!
! Overview:
!
! BLAYER reads a volume dataset from a 2-D or 3-D multiblock real gas flow
! solution and derives a one-layer set of results, some of which apply to the
! wall, and some to the edge of the boundary layer. Integral quantities are
! also calculated, including displacement thickness and momentum thickness.
! If a nonzero roughness height k is specified, Re-kk is also output along with
! density, |velocity|, and viscosity at height k. All results are plottable
! against the surface grid.
!
! BLAYER is a generalization of BLAYER_RESULTS without the handling of TPS
! tile data. It has been adapted from BLAYER2D and BLAYER3D, which were first
! adapted from BLAYER_RESULTS. A variable number of species is handled, along
! with (possibly) more than one temperature and additional flow quantities
! beyond those that are required as inputs.
!
! The program reads Tecplot files (ASCII only), or PLOT3D grid and function
! files (ASCII or binary), and writes Tecplot ASCII or binary files. The
! merger of BLAYER2D and -3D was prompted by an upgrade of the Tecplot_io
! package to handle Tecplot 360 auxiliary data records.
!
! This version introduces the extensible control file format that it should
! have employed from the start. Revised control has belatedly been prompted by
! a requirement to choose from three possible definitions of film coefficient,
! CH. One of these involves recovery enthalpy, which has hitherto not been
! output by BLAYER but is now among a new set of optional outputs. The edge
! enthalpy remains with other edge quantities. Free stream enthalpy appears in
! the printable output that should go to a log file (standard output) if it is
! defaulted from block 1, point (1,1,nk).
!
! Assumptions:
!
! > The surface is normally expected to be at k = 1 for all grid blocks,
! or j = 1 for the 2-D case. [Internally, 2-D arrays are treated as if
! they are dimensioned (1:ni, 1, 1:nk).] However, for each block, the
! program does look for the face or edge with the smallest average
! initial increment off it, and if necessary permutes the block to put
! the wall at the k = 1 position.
! [Overriding the automated wall detection is also possible, along with
! suppressing processing of blocks specified in ancillary control file
! blayer.inp.2, more on which below.]
!
! > The radial lines are sufficiently normal to the surface for the 1-D
! boundary layer edge detection method to make sense.
!
! > The flow quantities are given in SI units, at the grid-points, not cell
! centers, although the latter should still be OK.
!
! > Aft-body results are questionable: any boundary layer edge detection
! method used is likely to be thwarted by at least some of the enthalpy
! profiles in separated flows. The hybrid curvature-based method has a
! higher chance of producing a plausible result than the other methods.
!
! Boundary Layer Surface Option:
!
! In spite of the disclaimer about detecting the edge in wake regions,
! an option has been provided to save the calculated edge locations (and
! thicknesses) as a second surface dataset to help visualize results with
! dubiously large edge thicknesses.
!
! Input Volume Data Format (Tecplot ASCII or Plot3D):
!
! The original design choice to expect the input volume flow variables in
! a certain order has been retained because the possibility of identifying
! the variables by name is thwarted by the species names, which could be
! provided for any of species densities, species number densities, species
! mass fractions, or species mole fractions, among other Postflow options.
! Therefore, the expected order is density, pressure, T, [Tv,], species,
! velocities, total enthalpy, Mach number, viscosity, thermal conductivity
! if Tv is present, and zero or more extra variables, the first of which
! should be laminar Prandtl number if recovery enthalpy is requested.
!
! Tecplot ASCII Input Format (as from DPLR's Postflow with units requested):
!
! TITLE = ""
! VARIABLES = "x, m"
! "y, m"
! ["z, m"] for the 3-D case
! 1: "rho, kg/m^3" density
! 2: "p, Pa" pressure
! 3: "T, K" translational temperature
! [ : "Tv, K" vibrational temperature; the default is 1 temp.]
! : "c_N_2" 1 or more species densities
! : "c_O_2"
! : "c_N_O"
! : "c_N"
! : "c_O"
! [ : ::: more species if specified; the default is 5 sp.]
! : "u, m/s" velocity components
! : "v, m/s"
! : ["w, m/s"] for the 3-D case
! : "H0, J/kg" total enthalpy
! : "M" Mach number (unitless; double quotes still needed)
! : "mu, Pa.s" viscosity
! [ : "kappa, W/m.K" total thermal conductivity if # temperatures > 1]
! [ : ::: miscellaneous extras; the default is 0 extras]
! ZONE T="Zone 1"
! I=17, J=25, [K=81, ]ZONETYPE=Ordered
! DATAPACKING=BLOCK
! DT=(SINGLE SINGLE .................... SINGLE SINGLE )
! 6.64733315E+00 6.57563824E+00 6.48970469E+00 6.39077472E+00 6. ...
! : : : : :
!
! Note that if any variable names are delimited as here by double quotes
! in order to contain embedded blanks, then all must be so delimited,
! including M[ach number].
!
! Also, the other format written by DPLR's Postflow is handled:
!
! [Optional title]
! variables=x,y,[z,]rho,p,T,C_n2,C_o2,C_no,C_n,C_o,u,v,[w,]h,M,mu
! zone t="flow2|3d" F=point, i= 161 j= 157 k= 1|81
! 6.64733315E+00 6.57563824E+00 6.48970469E+00 6.39077472E+00 6. ...
! : : : : :
!
! PLOT3D Input Format (ASCII or Binary):
!
! File pairs xxx.g/xxx.f or (preferably) xxx.gu/xxx.fu are implied if the
! control file contains (in place of a Tecplot xxx.dat input volume file)
! a file named xxx.g or xxx.gu.
!
! For DPLR users, the Postflow file should use output format 3 and
!
! ivarp = 0 100 110 120 1000 150 151 [152] 132 154 50 [extras]
! or ivarp = 0 100 110 120 125 1000 150 151 [152] 132 154 50 52 [extras]
!
! for single-temperature and two-temperature solutions, respectively,
! analogous to the Tecplot format.
!
! Output Results (Tecplot ASCII or Binary File, One Zone Per Grid Block):
!
! Wall Boundary Layer Edge Optional Outputs
!
! x density [ Roughness ht. (k > 0.)
! y pressure density at height k
! s | z Te [ Tve] |velocity| " "
! density total enthalpy viscosity " "
! pressure u Re-kk ]
! temperature v [ theta ]
! [ Tvw ] [ w ] [ Re-theta ]
! total enthalpy Mach number [ Re-theta/Medge ]
! viscosity viscosity [ Delta* ]
! [ N2 species density [ N2 species density [ Velocity thickness ]
! O2 " " O2 " " [ Recovery enthalpy Hrec ]
! NO " " NO " "
! N " " N " "
! O " " O " "
! ?? " " ] ?? " " ]
! heat flux delta
! [ catalytic heat flux ] Re-ue
! tau_x CH
! tau_y [ kappae ]
! [ tau_z ] [ extras ]
! |tau|
! [ kappaw ]
! [ extras ]
!
! Entering k = 0. or enable_Re_kk = F suppresses the set of results
! related to roughness height. But the other optional outputs appear in
! the same third group in the order of the enable_* namelist controls.
!
! Optional Additional Output File (blayer_edge_surface.dat):
!
! x Calculated boundary layer edge coordinates ...
! y
! z
! delta ... and thicknesses
!
! Notes:
!
! 1: Input and output files are assumed to be binary if their names end
! in 'plt', else they are assumed to be ASCII (normally with a 'dat'
! extension). However, binary input is not an option as there are
! no associated utilities in the available tecio.a library.
!
! 2: The program distinguishes 2-D/3-D data by reading the input volume
! file header and looking for 'z' or 'Z' as the third variable name.
!
! 3: The 2-D case outputs running length in place of z, so the outputs
! are written as though they were 3-D. Note that running length is
! along the wall from the upstream edge of the current block.
! Obtaining cumulative running lengths across blocks is grid-specific
! but could presumably be derived within Tecplot from these outputs.
!
! NOTE CONCERNING ARC LENGTHS:
! Program SORT_SURFACE_SLICE available from the present author can
! determine cumulative arc lengths across block boundaries. First,
! use Tecplot to slice the dataset (typically at z = 1.e-6 m for a
! centerline cut). The sorting program can assemble the slice into
! a contiguous curve (or curves) and optionally insert arc lengths.
! These may also be treated as run lengths from the stagnation point
! if requested under some circumstances suited to capsules.
!
! NOTE CONCERNING SHOCK STAND-OFF DISTANCES:
! Orion practice is to add shock stand-off distance as an extra
! surface quantity appended to the BLAYER output via programs
! SHOCK_STAND_OFF and MERGE_FILES available from the present author.
!
! 4: Heat flux is not among the data inputs (problematic in the volume).
! At the wall, derive it from the surface temperature and the single
! emissivity input. For cold wall applications, DPLR's Postflow can
! help.
!
! NOTE: Ryan McDaniel can explain how to use a Tecplot macro to
! overwrite BLAYER heat fluxes with those from Postflow.
!
! MORE RECENTLY: A Tecplot structured surface dataset may now be
! supplied to replace the eps*sigma*T**4 formulation that assumes a
! radiative equilibrium BC at the wall. This serves as a work-around
! for cold-wall cases. Such a file should contain a variable with
! 'qw' in its name and have matching block dimensions, either cell-
! centered as from DPLR's Postflow, or vertex-centered.
!
! 5: Re-ue is the unit Reynolds # based on edge conditions. To obtain
! Re-theta or Re-kk, multiply it by theta or k (but see 6 and 7).
!
! 6: Re-kk is Reynolds # based on roughness height k & conditions at k,
! but using viscosity at the wall rather than at k. If k > 0., an
! Re-kk profile is written to standard output for the surface point
! indicated in the control file (following the enthalpy ratio profile
! also specified this way). The density, |velocity|, and viscosity
! at height k are also output with this option. Use enable_Re_kk = F
! or k = 0. to suppress this option.
!
! Reference for Re-kk:
!
! "Review and Synthesis of Roughness-Dominated Transition
! Correlations for Reentry Applications" by Daniel C. Reda,
! Journal of Spacecraft and Rockets, Vol. 39, No. 2, Mar-Apr 2002
!
! 7. Re-theta [/ edge Mach number] is required commonly enough that
! it may be requested among the optional outputs whether Re-kk is
! requested or not. Re-theta/Medge is appropriate if Medge > 1.
!
! 8. Velocity thickness can be requested, as can delta* (displacement
! thickness).
!
! 9. Program EXTRACT_BLAYER_DATA is available from the present author
! to help tabulate certain flow solution results from CFD points
! along a trajectory in readiness for curve fitting and padding to
! full time histories as needed for TPS sizing at some body point(s),
! one body point per run. Simply enter a control file like this:
!
! 1 163 ! (iblock, i) for a 2-D case
! 5 26 6 58 32 7 27 28 ! pw, qconv, Tw, CH, Hedge, Hw, tauwx, tauwy
! MHL-t52.0/blayer.dat ! Any number of BLAYER output files, to EOF
! MHL-t55.3/blayer.dat
! MHL-t57.9/blayer.dat
! MHL-t61.2/blayer.dat
! MHL-t64.2/blayer.dat
! MHL-t65.8/blayer.dat
! MHL-t70.0/blayer.dat
!
! This example would also append |tauw| as an additional column in
! the output, which is designed for MERGE_TABLES.
!
! Control File (command line argument 1) Namelist Description:
!
! &BLAYER_Controls
! &end
!
! volume_file ! Input volume file(s):
! ! *.dat ==> Tecplot ASCII dataset
! ! *.g | *.gu ==> Plot3D formatted | unformatted
! ! *.f ! *.fu is implied
! ! Default: vol-for-blayer.gu + vol-for-blayer.fu
!
! surface_file ! Optional input Tecplot surface dataset containing
! ! a qw variable:
! ! *.dat ==> use its qw values if the block
! ! dimensions match the volume;
! ! cell- or vertex-centered suited to
! ! cold wall cases
! ! none ==> assume radiative equilibrium:
! ! qw = emissivity*sigma*T**4
! ! Default: none
!
! output_file ! Tecplotable wall and edge output data name:
! ! *.dat ==> ASCII
! ! *.plt ==> binary
! ! Default: blayer.dat
!
! datapacking ! Output data ordering:
! ! POINT ==> variables(1:nv) at a point are
! ! contiguous in each zone
! ! BLOCK ==> surface(1:ni,1:nj) values are
! ! contiguous for each variable
! ! Default: POINT
!
! profile ! Type of total enthalpy ratio to use for
! ! edge detection:
! ! 1 ==> (H + Hshift) / (Hinf + Hshift)
! ! 2 ==> (H - Hwall) / (Hinf - Hwall)
! ! Default: 2
!
! nprofile ! Block number for sample profile written to
! ! standard out:
! ! Default: 0 (suppress the sample profile)
!
! iprofile, jprofile ! (i,j) of indicated block for sample profile:
! ! Default: (1,1)
!
! Hinf ! Total enthalpy to use for the normalized total
! ! enthalpy ratio:
! ! 0. ==> use the value from block 1,
! ! point (1,1,nk)
! ! /0. ==> use this value as Hinf in the enthalpy
! ! ratio (avoid -1. and -2.)
! ! -1. ==> use the (i,j,nk) value for profile
! ! (i,j) of each volume block
! ! -2. ==> use the peak value along each profile
! ! Default: 0.
!
! Hshift ! Total enthalpy used if profile choice is 1 to
! ! make all enthalpies positive; e.g.,:
! ! Hform(0K) for CO2 = 8932880.
! ! Default: 0. (as for air)
!
! Href ! Reference enthalpy to use in the definition of
! ! CH = qw / (Href - Hw):
! ! 1. ==> Href = Hinf
! ! 2. ==> Href = Hedge
! ! 3. ==> Href = Hrec
! ! Default: 1.
!
! edge_percentage ! % of the total enthalpy ratio defining the
! ! b.l. edge input to the traditional edge method:
! ! Default: 99.5
!
! edge_lower_limit ! % of free-stream total enthalpy below which the
! ! edge is assumed not to be:
! ! Default: 95.
!
! edge_method ! Edge detection method:
! ! TRADITIONAL ==> Plain search for
! ! edge_percentage of 1.
! ! (99.5%, say)
! ! HYBRID ==> Curvature-based step looks for
! ! peak profile curvature,
! ! followed by the traditional
! ! method looking for
! ! 0.995 * peak H ratio
! ! Default: HYBRID
!
! nspecies ! Number of species >= 0
! ! 0 ==> species-related variables are omitted
! ! from the volume data
! ! Default: 5
!
! ntemperatures ! Number of temperatures >= 1
! ! Default: 1
!
! nextras ! Number of variables beyond the essentials >= 0
! ! Default: 0
!
! laminar ! T | F ==> laminar | turbulent
! ! Default: T
!
! emissivity ! Emissivity used if qw is derived from radiative
! ! equilibrium BC
! ! Default: 0.85
!
! roughness_height ! Roughness height in meters for Re-kk:
! ! 0. ==> same as enable_Re_kk = F;
! ! Default: 0.001524 meters = 0.06 inches
!
! enable_Re_kk ! T ==> output Re-kk (if k = roughness_height > 0.);
! ! density, |velocity|, and viscosity at height k
! ! are also output;
! ! Default: T
!
! enable_Re_theta ! T ==> output theta and Re-theta
! ! Default: T
!
! enable_Re_theta_Medge ! T ==> output Re-theta/Medge; may be appropriate if
! ! Medge > 1.
! ! Default: F
!
! enable_delstar ! T ==> output displacement thickness, delta*
! ! Default: T
!
! enable_vel_thickness ! T ==> output velocity thickness
! ! Default: F
!
! enable_Hrec ! T ==> output recovery enthalpy:
! ! requires (laminar) Prandtl number as extra
! ! variable 1 in the volume data
! ! Default: T
!
! Optional Ancillary Control File blayer.inp.2:
!
! Unlike another namelist control variable, this control file allows use of
! short-hand ways of specifying multiple block numbers, as now explained:
!
! Line 1: Blocks to be suppressed
!
! If present, this file should contain a list of block numbers to suppress,
! in any obvious convenient form, on a single line. Examples:
!
! 11:16 or 11-16 would both expand to 11, 12, 13, 14, 15, 16
! 10 12 14:20 or any other such intelligible list, on line 1
!
! This first line can be empty, meaning no blocks are suppressed.
! If the file is not present, no blocks are suppressed.
! At present, "suppressed" means the blocks are not processed, but dummy
! results are written as output. This avoids possible confusion resulting
! from renumbering of blocks in the output.
!
! Lines 2-n: Overrides for the automated wall detection scheme
!
! A wing leading edge plug case encountered spacings finer off the faces
! surrounding the plug than off the plug, so the following override scheme
! has been provided. Enter one block/face pair per line starting at line 2.
! For example:
!
! 10:13 [or blank line 1 if no blocks are being suppressed]
! 2 5 [use the k = 1 face for blocks 2:5]
! 3 5
! 4 5
! 5 5
!
! Optional Ancillary Variable Names File blayer.inp.3 For PLOT3D Input Cases:
!
! If the input volume data are in PLOT3D form, the variable names for the
! species densities and any extra variables may be supplied or defaulted.
! To supply them, provide a file named blayer.inp.3 with one or two lines.
! The first line should contain all the species names. The second line
! should contain the names of any extra variables. All the other input
! variables are in known locations and hence can be hard-coded in BLAYER.
!
! Example blayer.inp.3 (11 species on line 1; pressure coef. and total
! mixture number density as extras on line 2):
!
! n2 o2 no no+ n2+ o2+ n o n+ o+ e
! C_p N_tot
!
! If either line is empty, the variable names are defaulted like this:
!
! sp_1 sp_2 sp_3 ..... sp_11
! xtra_1 xtra_2
!
! Recovery Enthalpy Discussion:
!
! The recovery enthalpy formulation is:
!
! Hrec = He + (r - 1)/2 ue**2 where r = (laminar Pr)**zeta
!
! and exponent zeta = 1/2 for laminar flow and 1/3 for turbulent flow.
!
! Note that laminar Prandtl number is used whether laminar = T or F.
! It should be provided as a first "extra" volume input variable.
!
! Film Coefficient CH Discussion:
!
! CH = qw / (Href - Hw) where Href may be any of Hinf, Hedge, or Hrec.
!
! Namelist control input Href = 1., 2., or 3. controls these options.
!
! Href is another output variable for the Hedge and Hrec cases. Hinf
! appears in the standard output, which should be saved as a log file.
!
! Boundary Layer Edge Strategy (Each Radial Line):
!
! See subroutine blayer_edge below. Briefly, a curvature-based scheme is
! use to locate the most likely edge region, then the traditional method
! (99.5%) is applied as a fraction of the PEAK IN THAT NEIGHBORHOOD.
! This is known as the HYBRID (two-stage) method. The plain TRADITIONAL
! method (usually the 99.5% location) is also an option via edge_method.
!
! Procedures:
!
! Tecplot_io package I/O module for Tecplot files
! xyq_io and xyzq_io I/O modules for PLOT3D files
! <numerous numerics utilities>
!
! History:
!
! 06/19/04 D. Saunders Initial implementation of BLAYER_RESULTS.
! 08/23/05 " " Last enhancement to BLAYER_RESULTS before the
! 2-D translation. (Introduced PERMUTE_BLOCK to
! handle the wall at any block face.)
! 11/05/05 " " Initial 2-D translation (5 species, not TPS tile
! handling, and no PLOT3D file I/O option).
! 11/15/05 " " Generalized # species, temperatures, and extras.
! 11/30/05 " " BLAYER3D adapted from BLAYER2D.
! 12/01/05 " " Introduced "edge_method" control to allow easy
! comparison with traditional 99.5% method.
! 12/07/05 " " Heat flux units are now W/m^2.
! 12/08/05 " " Delta* and theta formulations now use tangential
! velocities, not total velocity magnitudes;
! careful safeguarding of a stag. point is required.
! 01/17/06 " " Following experiments with curve fitting and
! iterating on the arc length scaling to overcome
! a known weakness in the edge calculation method
! (namely, profile curvatures are not independent of
! the arc length scaling), the best work-around so
! far is to adjust the curvature-based result by
! picking the location of 99.5% OF THE PROFILE PEAK
! IN THAT NEIGHBORHOOD. For clean 2-D data, this
! matches the traditional method; for 3-D data, it
! handles the fact that the total enthalpy ratios
! can differ significantly from 1 in the region of
! peak curvature.
! 02/03/06 " " Momentum thickness had an extra factor of
! |vtangent|/|vtangent(edge)| in the integral. Thanks
! to Frank Greene for noticing it looked wrong.
! 03/14/06 " " A wing leading edge plug case picked the wrong face
! of blocks above the plug. Therefore, make use of
! the optional ancillary control file to override the
! automated smallest-average-increment scheme.
! 07/07/06 " " The traditional edge method was not trapping non-
! monotonic enthalpy ratios properly.
! 07/21/06 " " Avoiding inverse interpolation in the traditional
! edge method was a bad idea: the 4-point spline
! method does not degrade as gracefully to 3 or 2
! points as was assumed. Profiles with overshoots
! are best handled by either linear interpolation or
! by the nonlinear inverse interpolation now used.
! 08/05/06 " " A simulation of the Shuttle in the LENS facility
! produced some bad profiles with Hwall = Hedge =
! Hinfinity, causing divides by zero for the film
! coefficient (now guarded against).
! 08/21/06- " " Merged BLAYER2D/-3D as BLAYER as part of upgrading
! 09/08/06 to the Tecplot 360 version of Tecplot_io.f90.
! 04/22/07 " " High-density cases (256 points off the wall) showed
! the k window around the curvature-based peak needs
! to be larger for larger nk. The root of this
! problem is spurious local curvature peaks, which
! are more likely with denser spacing. A bigger
! window for the traditional method should find the
! proper peak enthalpy ratio for denser meshes.
! 04/25/07 " " The species density names have been off by one.
! For ns = 1 (air), we get wall and edge densities
! output twice (rhow and airw for DPLR input) but it
! is not worth the trouble suppressing airw & aire.
! 05/17/07 " " Switched to finite difference derivatives for the
! initial curvature calculations at the data points,
! because they are not affected by far away data.
! 06/26/07 " " Non-uniform in-flow (as from an arc-jet nozzle)
! means cutting off data below Hnorm = 0.95 is not
! viable. Therefore, optional new inputs Hinf and
! Hignore are provided after the nx[tra] input.
! (Later: If Hignore > 0. is input, the second-step
! use of the traditional method - 99.5% of the peak
! in the edge neighborhood - is suppressed. This
! helps deal with severe in-flow non-uniformity but
! overlooks the fact that curvature is not independ-
! ent of the normalization/data scaling.)
! 08/26/07 " " Permuted blocks were having the output array's nk
! set to the volume value instead of being left at 1.
! 01/22/08 " " Mars atmosphere cases with negative total enthalpy
! values prompted another optional Hshift input in
! the control file to avoid shifting via Tecplot.
! 02/01/08 " " Todd White needed to normalize each profile by its
! peak, so optional input Hinf now has 4 choices.
! 06/24/08 " " Discontinuities towards the Shuttle wing tip were
! traced to profiles that straighten up short of 1.0
! before achieving 1.0. This means the heuristic
! size of the neighborhood of the peak curvature
! can include ~1.0 for one profile but not for a
! neighboring profile. Stage 2 of the edge method
! then seeks 99.5% of quite different peaks in those
! neighborhoods. Use of 99.5% means even small
! changes lead to large differences in edge thickness
! when the profile is so steep. Mike Olsen suggested
! using 95% to reduce the effect greatly, but then
! all edge-related quantities would be significantly
! lower everywhere. After much pondering, we stay
! with 99.5%, and accept that wing tip regions are of
! limited interest anyway, even on the wind side.
! 12/16/09 " " Arranged for Re-theta[/ Medge] output as an option
! via the roughness height control (-1. or -2.).
! 07/07/10 " " Dinesh noticed that Mars cases did not subtract the
! total enthalpy offset (needed for edge detection)
! from the interpolated enthalpies. Sorry!
! 01/26/11 " " Jay Hyatt asked if the surface formed by the
! locations of the estimated boundary layer edge
! points along each radial line could be saved for
! visualization. See the extended use of the
! output DATAPACKING control to invoke this option.
! 04/13/11 " " Trouble with a 2-D case from Jay Hyatt was traced
! to setting unit_normal(3), now set only if nd = 3.
! 09/10/12 " " Dinesh asked for velocity thickness as an option in
! place of displacement thickness. Usage of the
! roughness height input k has been made even more
! involved as a result (but avoids a new input).
! See Note 8 above for the details.
! 02/12/13 " " This version replaces the Hshift fix (01/22/08)
! by working with (H - Hwall)/(Hinf - Hwall).
! Any Hshift input is ignored, to avoid affecting
! existing input control files. But see Oct. 2017.
! 06/09/14 " " Belated merging of two changes: this version works
! with (H - Hw) / (Hinf - Hw) and the traditional
! method (if used) can save the indicated profile
! as originally implemented for the curvature-based
! method (only).
! Also, (x,y,z,f) output results for the body point
! specified in the control file are written to
! standard output.
! 06/11/14 " " Append output variable names to the list of results
! for the specified profile. Also, the upper k limit
! for both edge methods is now 4*nk/5 rather than
! 2*nk/3 (99.5% method) or 3*nk/4 (curvature method).
! Avoiding shock anomalies is the problem here.
! 08/28/14 " " CH (heat transfer coefficient) is now defined as
! qw/(Hinf - Hw), not qw/(Hedge - Hw), so as to be
! consistent with US3D developers. The issue is
! that Hedge cannot be trusted for aft-body points.
! 03/18/15 " " Ross Chaudhry at U. of Minnesota questioned use of
! CSDVAL with spline coefficients b1, c1, d1 for
! which the associated CSFIT call had been commented
! out, forgetting this usage. Somehow turning on
! all checks (-C with ifort) did not catch this,
! and other safeguards (including use of the 99.5%
! traditional method in the neighborhood of the
! curvature peak) masked the slip.
! Also:
! " " Retrofitted the PLOT3D input file option that had
! originally been handled by BLAYER_RESULTS.
! Introduced blayer.inp.3 to allow entry of names
! for the species and any extras for PLOT3D cases.
! 10/05/17 " " Merged the two choices of total enthalpy profile
! via the edge_method control, q.v.
! 10/11/17 " " Dinesh didn't like the way delstar and theta are
! zero at a stagnation point (possibly only for
! axisymmetric solutions). Therefore, trap zero
! delstar and, before results for that block are
! saved, extrapolate along the surface to the
! stag. point according to the recorded indices.
! Also: suppress duplicate profile output by the
! hybrid method (second stage was repeating what
! was already written by the first stage).
! 11/17/17 " " Raised tlimit in subroutine blayer_edge from 0.5
! to 0.7 on account of cases with nk = 101 (low) and
! thick boundary layers at high altitude. For the
! selected profile, a curvature-based preliminary
! Hedge was being updated by the traditional method
! before the save_plottable_details call.
! 03/23/23 " " Introduced optional surface-qw.dat file as a way
! of overriding the radiative equilibrium assumption
! long used to derive surface heat flux, which is not
! appropriate for cold wall cases. (But no longer
! used -- see namelist control suerface_file.)
! 03/25/23 " " After discussion with Dinesh Prabhu, an option to
! replace the output edge enthalpy with recovery
! enthalpy has been incorporated. It requires the
! input volume dataset to contain Prandtl number as
! a first "extra" variable, which in the case of DPLR
! means ivar = 88 for laminar flow or 98 for turb-
! ulent flow. This option requires the presence of
! ancillary file recovery-enthalpy.inp containing
! 0.5 or 0.3333333333.... on line 1 for laminar or
! turbulent flow. This is an exponent used in the
! derivation of Hrec from He as outlined above.
! The option is intended for compatibility with a
! material response solver.
! 03/27/23 " " Use of Hedge for the output total enthalpy at the
! edge was flawed. Hedge is used as a control for
! the edge method (but not after 04/23 revisions).
! April, 2023 " " Multiple CH options and introduction of recovery
! enthalpy belatedly led to abandoning the original
! control file scheme (increasingly difficult to
! extend while remaining backwardly compatible) and
! adopting a namelist control file scheme.
! 06/14/23 " " Fixed a glitch in the reading of unformatted
! Plot3D files.
! 10/31/23 " " Rude surprise for Halloween: Kaelan Hansson found
! that gfortran does not support getarg, advising
! that Fortran 2003 and later provides the similar
! get_command_argument (number [, value, length,
! status]) instead.
! 12/04/23 " " Dinesh asked for stag. point data to help set up
! equivalent calculations on a sphere. Since blocks
! are processed one at a time for efficiency, we need
! to track the minimum |tauw| within each block and
! update corresponding flow data whenever a lower
! block |tauw| is found. Initial efforts to do better
! than the best grid point were futile: any interp-
! olations within a quad. cell are bilinear, so a
! minimum can only appear at a vertex. Nonlinear
! interpolation across cells would be overkill, non-
! trivial, and suffer near block edges.
! 12/05/23 " " Use the x component of the body normal to avoid aft
! body blocks in the stagnation point search.
! 05/16/24 " " Subroutine look_for_surface_heat_flux was
! deallocating z from the heat flux file for both
! 2D and 3D cases. Sorry Chris!
!
! Author: David Saunders, ELORET Corporation/NASA Ames Research Center, CA
! Now with ERC, Inc. at NASA ARC (August 2010 through June 2015).
! Now with AMA, Inc. at NASA ARC.
!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!