cBit32 $SMEI/ucsd/gen/for/lib/bytes/cbit32.f
[Previous] [Next]
 NAME:
	cBit32
 PURPOSE:
	Put the binary representation for a integer*4 into a 32 character string array.
 CALLING SEQUENCE:
	character*32 function cBit32(IN)
 INPUTS:
	IN		integer*4	integer to be converted to/from binary
 CALLS: ***
	Bit32
 RESTRICTIONS:
	If IN is negative, twos complement convention is assumed, i.e. bit 16 is set
	to one; the other 15 bits are those of the positive number IN+32768.
 PROCEDURE:
	The least significant bit of IN is put into cBit32(32:32), the most 
	significant in cBit32{1:1).
 MODIFICATION HISTORY:
	MAR-1992, Paul Hick (UCSD/CASS; pphick@ucsd.edu) : Rewrite of JBIT16


cDbl2Str $SMEI/ucsd/gen/for/lib/str/cdbl2str.f
[Previous] [Next]
 NAME:
	cDbl2Str
 PURPOSE:
	Convert floating point number to string
 CATEGORY:
       Strings: write floating point number to string
 CALLING SEQUENCE:
	character*14 function cDbl2Str(Fin,Nin)
 INPUTS:
	Fin		double precision	floating point number to be converted
	Nin		integer			(see PROCEDURE)
 OUTPUTS:
	cDbl2Str	character*(*)		resulting string
 CALLS: ***
	Dbl2Str
 CALLED BY:
	smei_base, smei_cal, smei_orb, smei_skyd
 SEE ALSO:
	Dbl2Str
 RESTRICTIONS:
	cDbl2Str is a character*14  function
 PROCEDURE:
	See Flt2Str
 MODIFICATION HISTORY:
	AUG-1995, Paul Hick (UCSD)


cFilePath $SMEI/ucsd/gen/for/lib/str/cfilepath.f
[Previous] [Next]
 NAME:
	cFilePath
 PURPOSE:
	Platform-independent construction of file name
 CATEGORY:
	Portability
 CALLING SEQUENCE:
	character*256 function cFilePath(cRootDir,nSub,cSub,cFile)
 CALLS: ***
	iFilePath
 PROCEDURE:
	The length of the function is set equal to the value of
	parameter FIL__LENGTH in filparts.h
 MODIFICATION HISTORY:
	JUN-2004, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


cFlt2Str $SMEI/ucsd/gen/for/lib/str/cflt2str.f
[Previous] [Next]
 NAME:
	cFlt2Str
 PURPOSE:
	Convert floating point number to string
 CATEGORY:
       Strings: write floating point number to string
 CALLING SEQUENCE:
	character*14 function cFlt2Str(Fin,Nin)
 INPUTS:
	Fin		real		floating point number to be converted
	Nin		integer		(see PROCEDURE)
 OUTPUTS:
	cFlt2Str	character*(*)	resulting string
 CALLS: ***
	Flt2Str
 CALLED BY:
	Connect, HOSOrbID, HOSPlot, LOSReach, LOSWeights, Pandora, PrintAll, WR2DARR
	XMAP_SC_POS, XMAP_SC_POS8, nrRatInt, smei_frm_base, smei_frm_c3fudge, smei_frm_ped
	smei_frm_ped_guess, smei_frm_ratio
 SEE ALSO:
	Flt2Str
 RESTRICTIONS:
	cFlt2Str is a character*14  function
 PROCEDURE:
	See Flt2Str
 MODIFICATION HISTORY:
	AUG-1995, Paul Hick (UCSD)


Chebyshev $SMEI/ucsd/gen/for/lib/math/chebyshev.f
[Previous] [Next]
 NAME:
	Chebyshev
 PURPOSE:
	Evaluate value of Chebyshev polynomial in given point X
 CATEGORY:
	Math: orthogonal polynomials
 CALLING SEQUENCE:
	function Chebyshev(X,N)
 INPUTS:
	X		real		the Chebyshev polynomial is evaluated in X
	N		integer		degree of Chebyshev polynomial
 OUTPUTS:
	Chebyshev	real		value of n-th degree Chebyshev polynomial in XS
 RESTRICTIONS:
	The degree N must be larger/equal zero
 PROCEDURE:
	Evaluation is based three-term recurrence relation for Chebyshev 
	polynomials (T_0 = 1 ; T_1 = x)
	T_i = 2xT_i-1 - T_i-2 ; i = 2,3,4, ...
 MODIFICATION HISTORY:
	DEC-1991; Paul Hick (UCSD)


Chebyshev_exp $SMEI/ucsd/gen/for/lib/math/chebyshev_exp.f
[Previous] [Next]
 NAME:
	Chebyshev_exp
 PURPOSE:
	Given the coefficients of its expansion in Chebyshev polynomials, 
	evaluate the value of a polynomial in point X
 CATEGORY:
	Math: orthogonal polynomials
 CALLING SEQUENCE:
	function Chebyshev_exp(A,B,X,N,CN)
 INPUTS:
	A,B		real		definition interval (see PROCEDURE)
	X		real		X-value where function is evaluated
	N		integer		# terms in Chebyshev expansion
	CN(N)		real		expansion coefficients
 OUTPUTS:
	Chebyshev_exp	real		value of polynomial in point X
 RESTRICTIONS:
 >	The number of terms in the expansion, N, must be larger then zero
 >	A and B must be unequal
 PROCEDURE:
 >	The Chebyshev expansion is
	VALUE(X) = SUM(i=1,N) { CN(I)*T_i-1(XS) }, i.e. CN(I) is the
	coefficient of the Tchebyshev polynomial of degree I-1
 >	The interval [a,b] is mapped to [-1,1]. X is rescaled accordingly to
	XS = (2X-(B+A))/(B-A)
 >	The evaluation of the Tchebyshev polynomials is based on the
	three-term recurrence relation (T_0 = 1 ; T_1 = x)
	T_i = 2xT_i-1 - T_i-2 ; i = 2,3,4, ...
 MODIFICATION HISTORY:
	DEC-1991; Paul Hick (UCSD)


CheckMass $SMEI/for/lib/checkmass.f
[Previous] [Next]
 NAME:
	CheckMass
 CALLING SEQUENCE:
	subroutine CheckMass(XCbeg,XCend,V3D,D3D)
 CALLS: ***
	Flt2Str, Say, Str2Str, T3D_get_grid, T3D_iget, cosd, sind
 CALLED BY:
	SW_Model_Kinematic
 INCLUDE:
	include		'math.h'
	include		't3d_array.h'
	include		't3d_grid_fnc.h'
	include		't3d_loc_fnc.h'


cHideLogical $SMEI/ucsd/gen/for/lib/str/chidelogical.f
[Previous] [Next]
 NAME:
	cHideLogical
 PURPOSE:
	Hides the value of a logical from a fully qualified file specification
 CATEGORY:
	String handling
 CALLING SEQUENCE:
	character*256 function cHideLogical(cStr)
 INPUTS:
	cStr		character*(*)	Fully-qualified file name
 OUTPUTS:
	cHideLogical	character*(*)	File name with leading part replaced
					by the name of a logical.
 CALLS: ***
	iHideLogical
 CALLED BY:
	BField_Choose, BField_Get, ReadVIPS, ReadVIPSLOSCheck, ReadVIPSLOSCheckn
	ReadVIPSn, dailyips [1], dailyips [2], iSearch, smei_base, smei_orb
 RESTRICTIONS:
	Probably does not work on VMS
 PROCEDURE:
	If the input file is /home/soft/smei/test.txt, and
	logical $smei is defined as /home/soft/smei then the output
	string will be $smei/test.txt.

	The length of the function is set equal to the value of
	parameter FIL__LENGTH in filparts.h
 MODIFICATION HISTORY:
	JUN-2004, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


cInt2Str $SMEI/ucsd/gen/for/lib/str/cint2str.f
[Previous] [Next]
 NAME:
	cInt2Str
 PURPOSE:
	Write integer into string subject to constraints set by Int2StrSet
 CATEGORY:
	Strings: writing integer to string
 CALLING SEQUENCE:
	character*14 function cInt2Str(I)	! Same length as cFlt2Str
 INPUTS:
	I		integer		integer to be processed
 OUTPUTS:
	cInt2Str	character*(*)	output string
 CALLS: ***
	Int2Str
 CALLED BY:
	Connect, ForeignArg, HOSOrbID, HOSPlot, HOSPlot_bCommand, HOSRead, HOSUpdate, HOSWrite
	HOSdos2vms, LOSReach, NicHdr, OGetRecord, Pandora, SD, T3D_Read_B, dailyips [1]
	dailyips [2], iHOSInfo, iHOSRead, iHOSWrite, iOpenFile, rice, say_fts, smei_cal_c3mask
	smei_cal_get, smei_cal_init, smei_cal_read, smei_frm_path, smei_orb, smei_skyd
	smei_skyd_combine, smei_skyd_fill, smei_skyd_flush, smei_skyd_fts
	smei_skyd_init, smei_skyd_make, smei_skyd_pixel, smei_skyd_sky, smei_skyd_sort
 SEE ALSO:
	cFlt2Str
 PROCEDURE:
	cInt2Str is declared as a character*14 function
 MODIFICATION HISTORY:
	JAN-1995, Paul Hick (UCSD)


Clean0 $SMEI/ucsd/gen/for/lib/bytes/clean0.f
[Previous] [Next]
 NAME:
	Clean0
 PURPOSE:
	Cleans 'dirty' or 'NaN' REAL*4 zeros
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	subroutine Clean0 (idirty)
 INPUTS:
	X	real	value to be checked
 OUTPUTS:
	X	real	set to zero if it was a dirty zero
	I	integer		0: if the was not modified
				1: if the input was set to zero
 CALLS:
	(none)
 SEE ALSO:
	RClean, iClean0, iCleanNaN
 RESTRICTIONS:
	Should be called with REAL*4 argument!
 PROCEDURE:
	A dirty zero is tested by the condition
		iand(idirty,Z'0000FF80') .eq. 0

	The NaN value is tested by
		iand(idirty,Z'0000FF80') .eq. 0
 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


Connect $SMEI/user/pphick/for/main/connect.f
[Previous] [Next]
 NAME:
	Connect
 PURPOSE:
	Connects separate data files into one big file
 CATEGORY:
	I/O: Helios
 CALLING SEQUENCE:
	program Connect
 INPUTS:
 >	The input files contain records in the usual structure (PHOTO_DATA or
	90DEG_DATA). They should contain only one particular color, but may
	contain any number of photometers and filters.
 >	File names, start-, end- and transfer times (see procedure) 
	are read either from a file cFileL or from the keyboard.
 >	The file cFileL starts with an optional record containing two times
	TBeg and TEnd indicating that only data between these two time limits
	should be extracted. If this record is omitted TBeg=0 and TEnd=999.
	Each subsequent record contains a file name and the corresponding
	transfer time TNew, separated by a blank.
 >	All times are in day of year
 OUTPUTS:
	The output file name OUT (recl=37) is a 13 character string 'XYRLF_doy.ext'

	X	= A or B for HELIOS A or B respectively;
	YR	= the year of observation (i.e. 78 for 1978);
	L	= U,B,V for U/B/V light respectively;
	F	= 1 through 5 depending on the filter (if the file contains
		  15/30 deg photometer data); or
		= 9 if the file contains only 90 deg photometer data (see NOTE);
	doy	= the day of year for the earliest data point.
	ext	= ZLD for unnormalized data files (i.e. original zodiacal light
		  data); or
		= DAT for normalized data files

	The 90 deg data are optionally written to either a separate file
	(with a '9' as fifth character and recl 6) or are appended to the file
	OUT.
 CALLS: ***
	ArrI4Index, ArrI4Zero, ArrR4Copy, AskR4, AskWhat, AskYN, IndexR4, Int2Str, Say, Str2Str
	Str2StrSet, bOpenFile, cFlt2Str, cInt2Str, iFilePath, iFreeLun, iGetFileSpec, iHOSInfo
	iHOSRead, iHOSWrite, iPutFileSpec, iSetFileSpec, iUniqueName, iwhitespace
 INCLUDE:
	include		'dirspec.h'
	include		'filparts.h'
	include		'openfile.h'
	include		'str2str_inc.h'
	include		'hos_e9.h'
 RESTRICTIONS:
 >	A zodiacal light model may already be subtracted ('normalized' data),
	but not necesarily. All files should be of the same type: all or none
	of the files are normalized; all files should contain the same color;
	if this is not the case the program stops and no output is produced.
 >	WARNING: if you want to connect data from different years, say from
	december 1976 to january 1977, 366 days should be added to the times
	for the later year, e.g. doy 1.2345 of 1977 should become 367.2345.
	There is an option in PANDORA which does that.
 PROCEDURE:
 >	One specified filter will be extracted. The output file is sorted in
	time. (Note that the program can also be run on one file, to extract
	data for a specific time period, or to extract a specific filter).
 >	A period of time is covered by N subsequent (partly overlapping) data
	files, file I+1 containing data later than file I (I=1,..,N-1).
	Data will be copied to the output file using the following rules:
	(1) Only data inside an overall time window TBeg <= T <= TEnd are 
	    extracted
	(2) The switch from one data file to the next is made at transfer times
	    TNew, which have to be specified for each file except the last
	    (if a value is given it should be larger than 999).
 >	For the I-th file data will be copied for which
	TNew(I-1) <= T < TNew(I),
	where TNew(0) = TBeg and TNew(N) = TEnd;
	i.e. data up to the transfer time are copied; for the next file data
	from the transfer time onwards are copied.
 >	The output files are created in the directory where the first data file
	is found (usually, but not necessarily the working directory).
 MODIFICATION HISTORY:
	1989, Paul Hick (UCSD)


ConvertG2D $SMEI/for/lib/convertg2d.f
[Previous] [Next]
 NAME:
	ConvertG2D
 PURPOSE:
	Make a density map at a given height from a G-level map from the
	Hick et al. map technique.
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine ConvertG2D(ID,N,G,D,RR,D1AU,PW)
 INPUTS:
	ID		integer	mode - 0=standard, 1=input conversion
	N		integer	# data points
	G(N)		real	G-levels
	RR		real	Reference distance (AU)
	D1AU		real	1 AU density
	PW		real	Power
 OUTPUTS:
	D(N)		real	Density map at height RR
 CALLS: ***
	BadR4, GTODEN
 CALLED BY:
	ipsd, ipsdt
 PROCEDURE:
	Values in G = BadR4() are not converted (D is set to BadR4()).
	iGfnc = 0	(n=G)
	iGfnc = 1	(Tappin, n=9xG^2)
	iGfnc = 2	(n=10.4xG^3.4)
	iGfnc = 3	(n=9.5xG^5.1)
 MODIFICATION HISTORY:
	NOV, 1995 B. Jackson (STEL,UCSD)


CopyDtoDVN $SMEI/for/ipsdt/copyvtovdn.f
[Previous] [Next]
 NAME:
	CopyDtoDVN
 PURPOSE:
	Make density maps at the velocity map time cadence. Velocity and density maps of the same latitude and longitude 
	grid spacing must be input. The Carrington rotation beginning and endings at each time are imput, but can change 
	with time as long as their interval lengths remain constant.  Thus, either a corotating (tested) or an inertial
	set of maps can be converted.
	If Mode = 0, then only an interpolated value of the density map is transferred.
	If Mode = 1, then an interpolated value of the density map is transferred plus an interpolated map out to many
		sigma in time at that longitude.
	If Mode = 2, then the interpolated value is cut off at the 1.5 times the velocity temporal interval - 
		i.e. one time from the non-valid value in time.
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	call CopyDtoDVN(Mode,XCbe,XCtbeg,XCtend,XCtbegG,XCtendG,nLng,nLat,nTG,nTV,ConsT,DD,DDV,DDT,DDD)
 INPUTS:
	Mode		   integer	0 - transfer good time values only
					1 - transfer both good and average time values
					2 - Same as 1, but cut off filter after 1 time away
	XCbe		   real		Beginning V times (XCbeV)
	XCtbeg		   real*8	Beginning V time (XCtbegV)
	XCtend		   real*8	Ending V time (XCtendV)
	XCtbegG		   real*8	Beginning G time
	XCtendG		   real*8	Ending G time
	nLng		   integer	# Longitude points
	nLat		   integer	# Latitude points
	nTG		   integer	# G-level times
	nTV		   integer	# velocity times
	ConsT		   real		Time filter constant (in terms of the velocity time interval)
	DD(nLng,nLat,nTG)  real		Density map
 OUTPUTS:
	DDV(nLng,nLat,nTV) real		Density map interpolated at the velocity time cadence
 SCRATCH ARRAYS:
	DDT(nTG)	   real
	DDD(nLng)	   real
 CALLS: ***
	BadR4, FLINT
 CALLED BY:
	ipsdt
 PROCEDURE:
	Bad values (indicated by BadR4()) are not processed in Mode 0
 MODIFICATION HISTORY:
	NOV, 1999 B. Jackson (STEL,UCSD)


CopyVtoVDN $SMEI/for/ipsdt/copyvtovdn.f
[Previous] [Next]
 NAME:
	CopyVtoVDN
 PURPOSE:
	Make velocity maps at the density map time cadence. Velocity and density maps of the same latitude and longitude 
	grid spacing must be input. The Carrington rotation beginning and endings at each time are imput, but can change 
	with time as long as their interval lengths remain constant.  Thus, either a corotating (tested) or an inertial
	set of maps can be converted.
	If Mode = 0, then only an interpolated value of the velocity map is transferred.
	If Mode = 1, then an interpolated value of the velocity map is transferred plus an interpolated map out to many
		sigma in time at that longitude.
	If Mode = 2, then the interpolated value is cut off at the 1.5 times the density temporal interval - 
		i.e. one time from the non-valid value in time.
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	call CopyVtoVDN(Mode,XCbe,XCtbeg,XCtend,XCtbegV,XCtendV,nLng,nLat,nTV,nTG,ConsT,VV,VVD,VVT,VVV)
 INPUTS:
	Mode		   integer	0 - transfer good time values only
					1 - transfer both good and average time values
					2 - Same as 1, but cut off filter after 1 time away
	XCbe		   real		Beginning G (XCbeGG)
	XCtbeg		   real		Beginning G time (XCtbegG)
	XCtend		   real		Ending G time (XCtendG)
	XCtbegV		   real		Beginning V time (XCtbegV)
	XCtendV		   real		Ending V time (XCtendV)
	nLng		   integer	# Longitude points
	nLat		   integer	# Latitude points
	nTV		   integer	# velocity times
	nTG		   integer	# G-level times
	ConsT		   real		Time filter constant (in terms of the density time interval)
	VV(nLng,nLat,nTV)  real		Velocity map
 OUTPUTS:
	VVD(nLng,nLat,nTG) real		Density velocity map
 SCRATCH ARRAYS:
	VVT(nTV)	   real
	VVV(nLng)	   real
 CALLS: ***
	BadR4, FLINT
 CALLED BY:
	ipsdt
 PROCEDURE:
	Bad values (indicated by BadR4()) are not processed in Mode 0
 MODIFICATION HISTORY:
	NOV, 1999 B. Jackson (STEL,UCSD) Found error 11/14/00 in determining first part BVJ


cosd $SMEI/ucsd/gen/for/os/goniod.f
[Previous] [Next]
 NAME:
	cosd
 PURPOSE:
	Goniometric function accepting arguments in degrees
 CATEGORY:
	Math
 CALLING SEQUENCE:
	function cosd(a)
 INPUTS:
	a,b	real			angle in degrees
	c,d	double precision	angle in degrees
 OUTPUTS:
	S	real			angle in degrees
	D	double precision	angle in degrees
 CALLED BY:
	AsymDust, CheckMass, CosdLookup, DustAsymmetry, ElSunDistance, HOSOrbID, KeplerOrbit
	MkDMap, MkDMaptdn, MkLOSWeights, MkPos, MkPostd, MkVMap, MkVMaptdN, PA_POLE, PointPOnLOS
	PointPOnLOS_Near, PointPOnLOS_Reset, ReadG, SC_ECLIP, SC_ECLIP90, SphereWeight
	THOM_WTF, ThomsonLOS, ThomsonLOS3D, ThomsonLOS3DStep, ThomsonMidpoint
	ThomsonMidpointFar, Time2PrecesssionLtd, Write3D_bb, Write3D_bb_UT
	Write3D_bb_XC, Write3D_bbtt, Write3D_nv_UT, iProcessOoty, iProcessOotyn
	iProcessUCSD, iReadOoty, iReadOotyn, iReadUCSD
 INCLUDE:
	include     'math.h'
 SEE ALSO:
	acosd, asind, atan2d, atand, dacosd, dasind, datan2d, datand, dcosd, dsind, dtand, sind, tand
 RESTRICTIONS:
	Note that it probably will be necessary to declare the function
	type explicitly in the calling program, e.g.

	real			acosd, cos
	double precision	dacosd, dcos
 PROCEDURE:
	Can be used with Fortran compilers that do not provide goniometric
	function accepting input and providing output in degrees (e.g. g77).
 MODIFICATION HISTORY:
	JAN-2001, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


CosdLookup $SMEI/ucsd/gen/for/lib/math/cosdlookup.f
[Previous] [Next]
 NAME:
	CosdLookup
 PURPOSE:
	Calculates cos(x) using lookup table
 CATEGORY:
	Math
 CALLING SEQUENCE:
	function CosdLookup(X)
 INPUTS:
	X		real		X-coordinate
 OUTPUTS:
	F		real		cos(x) from table lookup
 CALLS: ***
	FLINT, cosd
 SEE ALSO:
	GaussLookup, SinLookup
 MODIFICATION HISTORY:
	SEP-2003, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


cotri $SMEI/for/h/cotri.h
[Previous] [Next]
 NAME:
	cotri
 PURPOSE:
	include file used by HELIM program


crx_ped_dark_cam1_v1 $SMEI/ucsd/camera/for/base/original/crx_ped_dark_cam1_v1.f
[Previous] [Next]
 name:		CRX_ped_dark_cam1.for
 purpose:	determines pedestal & dark current, finds measles
 inputs:	*.nic data files listed in "namelist2.txt"
 outputs:	before and after *.grd files 
    "		Note here that the pedestal, dark, and CR information incorporated into the "trailer"
    "		The output files xxx.dat,txt present information for graphs/subseq of the various quantities
 calls:	subroutines  measles (+ plane), and INDEXX (2 versions) 
 mods:		April 2004, Andrew Buffington (UCSD; (858)-534-6630; abuffington@ucsd.edu)


crx_ped_dark_cam2_v1 $SMEI/ucsd/camera/for/base/original/crx_ped_dark_cam2_v1.f
[Previous] [Next]
 name:		CRX_ped_dark_cam2.for
 purpose:	determines pedestal & dark current, finds measles
 inputs:	*.nic data files listed in "namelist2.txt"
 outputs:	before and after *.grd files 
    "		Note here that the pedestal, dark, and CR information incorporated into the "trailer"
    "		The output files xxx.dat,txt present information for graphs/subseq of the various quantities
 calls:	subroutines  measles (+ plane), and INDEXX (2 versions) 
 mods:		April 2004, Andrew Buffington (UCSD; (858)-534-6630; abuffington@ucsd.edu)


CRX_ped_dark_cam3.for $SMEI/ucsd/camera/for/base/original/crx_ped_dark_cam3_v2.f
[Previous] [Next]
 NAME:
	CRX_ped_dark_cam3.for
 PURPOSE:
	determines pedestal & dark current, finds black/white measles & cosmic rays
 INPUTS:
	*.nic data files listed in "namelistCRX.txt"
 OUTPUTS:
	before and after *.grd files 
	Note here that the pedestal, dark, and CR information incorporated into the "trailer"
	The output file xxx.dat presents information for graphs of the various quantities
 CALLS:
	and INDEXX, subroutines  measles (+ plane)
 MODIFICATION HISTORY:
	January 2004, Andrew Buffington (UCSD; (858)-534-6630; abuffington@ucsd.edu)
	Please Note that "headroom" and small-scale FF are turned OFF when camera 3 in 2x2 mode as here...
	Another consequence of this is that columns 11 and 631 are NOT half stamped out as would be
	the case if the SSFF were imposed. Thus these have a full amount of pedestal and dark current,
	but only an unknown and variable-with-row fraction of sky between 0.5 and unity. Yuck!


cTime2Str $SMEI/ucsd/gen/for/lib/time/ctime2str.f
[Previous] [Next]
 NAME:
	cTime2Str
 PURPOSE:
	Convert time to specified string format
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	character*80 function cTime2Str(cFmt,t)
 OUTPUTS:
	u(2)		integer		rounded 2-element standard time
 CALLS: ***
	Time2Str
 CALLED BY:
	jpl_message, smei_cal_get, smei_cal_init, smei_frm_c3fudge, smei_frm_ratio
 MODIFICATION HISTORY:
	JAN-2004, Paul Hick (pphick@ucsd.edu)


cTime2System $SMEI/ucsd/gen/for/lib/time/ctime2system.f
[Previous] [Next]
 NAME:
	cTime2System
 PURPOSE:
	Get system time in specified string format
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	character*80 function cTime2System(cFmt)
 OUTPUTS:
	u(2)		integer		rounded 2-element standard time
 CALLS: ***
	Time2Str, Time2System
 CALLED BY:
	ExtractInsitu, Extractd, Extractd3d, Say, StopWatch, WR2DARR, iUniqueName, sprint
 MODIFICATION HISTORY:
	JAN-2004, Paul Hick (pphick@ucsd.edu)


CvD2G $SMEI/for/lib/cvd2g.f
[Previous] [Next]
 NAME:
	CvD2G
 PURPOSE:
	Convert between normalized density nr^2 and g^2
 CATEGORY:
	Tomography
 CALLING SEQUENCE:
	subroutine CvD2G(PWN,N,DD,G2)
 INPUTS:
	PWN	real
	N	integer		# values to be converted
				N < 0 : check for bad values (BadR4())
	DD(N)	real		normalized densities
 OUTPUTS:
	G2(N)	real		g^2 values
 CALLS: ***
	BadR4
 CALLED BY:
	SW_Model_Kinematic, ipsg2, ipsg2s, ipsg2t
 PROCEDURE:
	The relation between g^2 and normalized density:
		G2 = DD^(2*PWN)
	If N < then bad values in the output array will also be
	bad in the output array.
 MODIFICATION HISTORY:
	MAY-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


cvdim $SMEI/for/h/cvdim.h
[Previous] [Next]
 NAME:
	cvdim
 PURPOSE:
	Include file used by contour plotting routines CVPLOT and CVYN


CvG2D $SMEI/for/lib/cvg2d.f
[Previous] [Next]
 NAME:
	CvG2D
 PURPOSE:
	Convert from g^2 to normalized density nr^2
 CATEGORY:
	Tomography
 CALLING SEQUENCE:
	subroutine CvG2D(PWN,N,G2,DD)
 INPUTS:
	PWN	real
	N	integer		# values to be converted
				N < 0 : check for bad values (BadR4())
	G2(N)	real		g^2 values
 OUTPUTS:
	DD(N)	real		normalized densities
 CALLS: ***
	BadR4
 CALLED BY:
	SW_Model_Kinematic, Write3D_nv_UT, Write3D_nv_XC, ipsg2, ipsg2s, ipsg2t
 PROCEDURE:
	The relation between g^2 and normalized density:
		G2 = DD^(2*PWN)
	If N < then bad values in the output array will also be
	bad in the output array.
 MODIFICATION HISTORY:
	MAY-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


CvI2 $SMEI/ucsd/gen/for/lib/bytes/cvi2.f
[Previous] [Next]
 NAME:
	CvI2
 PURPOSE:
	Convert integer*2 numbers between VMS, DOS & UNIX
 CALLING SEQUENCE:
	subroutine CvI2(cOp,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	N	integer		# elements in XX
	XX(N)	integer*2	array
 OUTPUTS:
	XX(N)	integer*2	converted array
 CALLED BY:
	iHOSRead, iHOSWrite
 RESTRICTIONS:
	cOp should correspond to an entry in the include file 'dirspec.h'.
 INCLUDE:
	include		'dirspec.h'
 CALLS: ***
	CvSwap
 PROCEDURE:
	Byte swapping


CvI4 $SMEI/ucsd/gen/for/lib/bytes/cvi4.f
[Previous] [Next]
 NAME:
	CvI4
 PURPOSE:
	Convert integer*4 numbers between VMS, DOS & UNIX
 CALLING SEQUENCE:
	subroutine CvI4(cOp,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	N	integer		# elements in XX
	XX(N)	integer*4	array
 OUTPUTS:
	XX(N)	integer*4	converted array
 CALLED BY:
	jpl_close, jpl_init, jpl_state
 RESTRICTIONS:
	cOp should correspond to an entry in the include file 'dirspec.h'.
 INCLUDE:
	include		'dirspec.h'
 CALLS: ***
	CvSwap
 PROCEDURE:
	Byte swapping


cvntvms $SMEI/user/pphick/for/main/cvntvms.f
[Previous] [Next]
 NAME:
	cvntvms
 CALLS: ***
	CvR4S, CvR8S


CvR4 $SMEI/ucsd/gen/for/lib/bytes/cvr4.f
[Previous] [Next]
 NAME:
	CvR4
 PURPOSE:
	Converts real*4 numbers between VMS, DOS and Unix
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	subroutine CvR4(cOp,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	N	integer		# elements in XX
	XX(N)	real*4		array
 OUTPUTS:
	XX(N)	real*4		converted array
 CALLS: ***
	CvSwap
 CALLED BY:
	HERDISK, iHOSArch, iHOSRead, iHOSWrite
 RESTRICTIONS:
	cOp should correspond to an entry in the include file 'dirspec.h'.
	Supported are 'DOS' (DOS/WIN/NT), 'UNX' (unix), 'VMS' and 'LNX' (Linux).
 INCLUDE:
	include		'dirspec.h'
	include		'math.h'
 PROCEDURE:
	Usually the numbers are converted to the native OS (i.e. the OS specified
	in 'dirspec.h'), and only the OS of origin needs to specified.
	CvR4S and CvR8S allow specification of both origin and destination OS
	for the conversion.
	(This setup is not that great. Number representation is more a matter of
	hardware architecture than OS. E.g. Linux and DOS/Windows running on Intel
	or AMD use the same number representations. So we should be testing for
	CPU architecture rather than OS. This is left as an excersize to the reader,
	I suppose).

 	INTEGER CONVERSIONS:

	VMS and DOS use the same representation for integers.
	Unix has the bytes in the opposite order relative to VMS and DOS (I think)
	Linux is the same as DOS.

 	REAL CONVERSIONS:

	The only difference between DOS and Unix appears to be that the order of the
	bytes is reversed (as for integers).
	Linux is the same as DOS.

	The real work is the conversion between DOS and VMS and v.v.

	Real*8 structure (64 bits):
	<------------------------ fraction -----------------> S<--- Exp --><-->	VMS
	S<--- Exp --><-------------------- fraction -------------------------->	INTEL
	32109876 54321098 76543210 98765432 10987654 32109876 54321098 76543210

	Real*4 structure (32 bits):
	<--- fraction --> S<- Exp -><----->	VMS
	S<- Exp -><--- fraction ---------->	INTEL
	10987654 32109876 54321098 76543210

	For both real*4 and real*8 the position of exponent and fraction in VMS and DOS
	are matched by reversing the order of the 2-byte words. 

 	Real*8 (G-floating) numbers originating on the VAX have the following structure:
	Bit 0..3,16..63 : normalized 52-bit fraction; the 53th bit (J-bit) is omitted, and is
		always 1, i.e. the numbers are always normalized
	Bit 4..14	: 11-bit biased exponent (biasing constant is 1025)
	Bit 64		: sign bit

	Real*8 for the INTEL FPU have the following structure
	Bit 0..51  : normalized 52-bit fraction; the 53th bit (J-bit) is omitted, but contrary to
		the VAX it can be zero (for very small, 'denormalized', numbers).
	Bit 52..62 	: 11-bit biased exponent (biasing constant is 1023)
	Bit 63     	: sign bit

 	Real*4 (F-floating) numbers originating on the VAX have the following structure:
	Bit 0..6,16..31 : normalized 24-bit fraction; the 24th bit (J-bit) is omitted, and is
		always 1, i.e. the numbers are always normalized
	Bit 7..14	: 8-bit biased exponent (biasing constant is 129)
	Bit 15		: sign bit
	As far as I can tell the exponent is always non-zero (1<=exp<=255), except for the
	number zero (when all bits are zero). An exponent of zero combined with a non-zero fraction
		are not valid real numbers.

	Real*4 for the INTEL FPU have the following structure
	Bit 0..22  : normalized 24-bit fraction; the 24th bit (J-bit) is omitted, but contrary to
		the VAX it can be zero (for very small, 'denormalized', numbers).
	Bit 23..30 	: 8-bit biased exponent (biasing constant is 127)
	Bit 31     	: sign bit

	VAX -> INTEL:
	The VAX structure is mapped to the INTEL structure by reversing the order of the
	words (2 for real*4, 4 for real*8.
	The VAX exponent is usually two more than the INTEL exponent (the difference of the
	biasing constants). If after subtraction of 2 the exponent is still positive, the
	subtraction completes the conversion from a VAX to an INTEL real*4 or real*8. If the
	corrected exponent is 0 or -1 than the INTEL real is denormalized and the fraction
	must be updated also. This is done by shifting the bits in the fraction downward
	(decreasing). Note that this means that the J-bit is shifted into the 'visible' 23-
	or 52-bit part of the fraction.

	INTEL -> VMS:
	The Intel architecture uses exponent 255 (real*4) and 2047 (real*8) for special
	purposes: quiet NaN, signal NaN, plus and minus infinity. These are not available
	on VMS. These values will be set to the parameter values MATH__NARN or MATH__NARN8
	and +/-MATH__PINF or +/-MATH__PINF8 defined in include file math.h.
	Numbers with exponent 254 (real*4) and 2046 (real*8) are outside the range of
	real values covered by VMS, and are set to +/-MATH__PINF or +/-MATH__PINF8.
	Numbers with exponent in the range [1,253] (real*4) and [1,2045] (normalized numbers)
	are converted to VMS by adding 2 to the exponent.
	Numbers with exponent 0 (denormalized numbers) can be normalized on the VMS only
	if the fraction can be made >=1 by shifting bits at most 2 positions. If it takes
	more than 2 the number will be set to zero.
 MODIFICATION HISTORY:
	OCT-1998, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
 TEST PROGRAM
	program test
	include		'dirspec.h'
	include		'openfile.h'
	include		'math.h'

	character	cOp*3
	logical		bWrite

	real*4		xx
	real*8		dd
	integer		i4(2)
	equivalence	(dd,i4),(xx,i4)

	real*4		xdos
	real*8		ddos
	integer		idos(2)
	equivalence	(ddos,idos),(xdos,idos)

	real*4		xvms
	real*8		dvms
	integer		ivms(2)
	equivalence	(dvms,ivms),(xvms,ivms)

	dd = MATH__NARN8

	cOp = OS__VMS
	if (cOpSys .eq. OS__VMS) cOp = OS__DOS

	xx = .29E-36

	I0 = I
	do while (I-I0 .lt. 60)
	    I = I+1

	    ii = 0
	    if (cOpSys .eq. OS__DOS) call MVBITS(i4(1),23,8,ii,0)
	    if (cOpSys .eq. OS__VMS) call MVBITS(i4(1), 7,8,ii,0)

	    xvms = xx
	    call CvR4S(cOpSys,cOp,1,xvms)

	    xdos = xvms
	    call CvR4S(cOp,cOpSys,1,xdos)

	    print *, ' exp ',ii, xx, xdos, xdos-xx, idos(1)-i4(1)

	    xx = xx/1.1
	end do

	xx = MATH__PINF/100.
	I0 = I

	do while (I-I0 .lt. 10)
	    I = I+1

	    ii = 0
	    if (cOpSys .eq. OS__DOS) call MVBITS(i4(1),23,8,ii,0)
	    if (cOpSys .eq. OS__VMS) call MVBITS(i4(1), 7,8,ii,0)

	    xvms = xx
	    call CvR4S(cOpSys,cOp,1,xvms)

	    xdos = xvms
	    call CvR4S(cOp,cOpSys,1,xdos)

	    print *, ' exp ',ii, xx, xdos, xdos-xx, idos(1)-i4(1)

	    if (cOpSys .ne. OS__VMS .or. xx .lt. MATH__PINF/2.) xx = xx*2
	end do

	dd = 0.56D-306
	I0 = I
	do while (I-I0 .lt. 60)
	    I = I+1

	    ii = 0
	    if (cOpSys .eq. OS__DOS) call MVBITS(i4(2),20,11,ii,0)
	    if (cOpSys .eq. OS__VMS) call MVBITS(i4(1), 4,11,ii,0)

	    dvms = dd
	    call CvR8S(cOpSys,cOp,1,dvms)

	    ddos = dvms
	    call CvR8S(cOp,cOpSys,1,ddos)

	    print *, ' exp ',ii, dd, ddos, ddos-dd, idos(1)-i4(1), idos(2)-i4(2)

	    dd = dd/1.1d0
	end do

	dd = MATH__PINF8/100.
	I0 = I

	do while (I-I0 .lt. 10)
	    I = I+1

	    ii = 0
	    if (cOpSys .eq. OS__DOS) call MVBITS(i4(2),20,11,ii,0)
	    if (cOpSys .eq. OS__VMS) call MVBITS(i4(1), 4,11,ii,0)

	    dvms = dd
	    call CvR8S(cOpSys,cOp,1,dvms)

	    ddos = dvms
	    call CvR8S(cOp,cOpSys,1,ddos)

	    print *, ' exp ',ii, dd, ddos, ddos-dd, idos(1)-i4(1), idos(2)-i4(2)

	    if (cOpSys .ne. OS__VMS .or. dd .lt. MATH__PINF8/2) dd = dd*2d0
	end do

	end


CvR4S $SMEI/ucsd/gen/for/lib/bytes/cvr4.f
[Previous] [Next]
 NAME:
	CvR4S
 PURPOSE:
	Convert real*4 numbers between VMS, DOS & UNIX
 CALLING SEQUENCE:
	entry CvR4S(cOp,cOpDest,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	cOpDest	character*3	operating system to be converted to
	N	integer		# elements in XX
	XX(N)	real*4		array
 OUTPUTS:
	XX(N)	real*4		converted array
 CALLED BY:
	cvntvms
 RESTRICTIONS:
	cOp and cOpDest should correspond to an entry in the include file 'dirspec.h'.
 CALLS: ***
	CvSwap
 PROCEDURE:
	See CvR4


CvR8 $SMEI/ucsd/gen/for/lib/bytes/cvr8.f
[Previous] [Next]
 NAME:
	CvR8
 PURPOSE:
	Convert real*8 numbers between VMS, DOS & UNIX
 CALLING SEQUENCE:
	subroutine CvR8(cOp,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	N	integer		# elements in XX
	XX(N)	real*8		array
 OUTPUTS:
	XX(N)	real*8		converted array
 CALLED BY:
	jpl_close, jpl_init, jpl_state
 RESTRICTIONS:
	cOp should correspond to an entry in the include file 'dirspec.h'.
 INCLUDE:
	include		'dirspec.h'
	include		'math.h'
 CALLS: ***
	CvSwap
 PROCEDURE:
	See CvR4


CvR8S $SMEI/ucsd/gen/for/lib/bytes/cvr8.f
[Previous] [Next]
 NAME:
	CvR8S
 PURPOSE:
	Convert real*8 numbers between VMS, DOS & UNIX
 CALLING SEQUENCE:
	entry CvR8S(cOp,cOpDest,N,XX)
 INPUTS:
	cOp	character*3	operating system where the numbers originated
	cOpDest	character*3	operating system to be converted to
	N	integer		# elements in XX
	XX(N)	real*8		array
 OUTPUTS:
	XX(N)	real*8		converted array
 CALLED BY:
	cvntvms
 RESTRICTIONS:
	cOp and cOpDest should correspond to an entry in the include file 'dirspec.h'.
 CALLS: ***
	CvSwap
 PROCEDURE:
	See CvR4


CvSwap $SMEI/ucsd/gen/for/lib/bytes/cvswap.f
[Previous] [Next]
 NAME:
	CvSwap
 PURPOSE:
	Swapping bytes
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	subroutine CvSwap(IB,NB,NN,X)
 INPUTS:
	IB	integer		# bytes treated as single unit (1,2 or 4)
	NB	integer		# bytes in one element of X (1,2,4 or 8)
				(1 for byte, 2 for integer*2, 4 for integer*4 and real*4,
				8 for real*8)
	NN	integer		# elements in X
	X(NB,NN)integer*1	declared as integer*1 array, but can be anything
 OUTPUTS:
	X(NB,NN)integer*1	input array with bytes swapped
 CALLS:
	(none)
 CALLED BY:
	CvI2, CvI4, CvR4, CvR4S, CvR8, CvR8S, HOSInquire, OCv2Flt, iHOSRead, iHOSWrite
 EXAMPLE:
	For integer*4 array I(10)
		call CvSwap(1,4,10,I)
	will reverse the order of bytes in each element of I (bytes 1,2,3,4 -> 4,3,2,1)
		call CvSwap(2,4,10,I)
	will reverse the order of words in each element of I (bytes 1,2,3,4 -> 3,4,1,2)
 PROCEDURE:
 MODIFICATION HISTORY:
	SEP-1998, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


cXCvarFormat $SMEI/for/lib/xcvarformat.f
[Previous] [Next]
 NAME:
	cXCvarFormat
 PURPOSE:
	Provides format specification for Carrington variables.
 CATEGORY:
	I/O
 CALLING SEQUENCE:
	character*9 function cXCvarFormat(NCoff,XC)
 INPUTS:
	NCoff		integer		Carrington rotation offset
	XC		real		Carrington variable with NCoff subtracted
 OUTPUTS:
	cXCvarFormat	character*9	string of type 1234.5678 (i.e. F9.4 format)
 CALLS: ***
	XCvarFormat
 CALLED BY:
	BListAll, MapReadSingle, MapReadTimes, T3D_Read_B
 MODIFICATION HISTORY:
	OCT-2003, Paul Hick (UCSD/CASS; pphick@ucsd.edu)