libarg $SMEI/user/pphick/for/main/libarg.f
[Previous] [Next]
 NAME:
	libarg
 PURPOSE:
	Extract command line switches from foreign input strings
 CALLING SEQUENCE:
	program libarg
 INPUTS:
	Foreign input from command line
	If not foreign input is provided the symbol array P1,..,P8 is processed
 OUTPUTS:
	To local symbols P1,..,P8 and ARG, or to local symbols specified
	as command line arguments
 CALLS: ***
	ForeignInput, Say, iGetSymbol [1], iGetSymbol [2], iSetSymbol [1], iSetSymbol [2]
	itrim
 RESTRICTIONS:
 >	The individual entries in the foreign input should not exceed 20 chars
 PROCEDURE:
	On VMS:
	$ $EXE:LIBARG SYMBOL1 SYMBOL2 .....
 >	After the switches have been removed, the remaining strings are put
	sequentially into P1,..,P8 until no strings remain. Trailing values
	in the P'I symbol array that do not receive any string are explicitly
	set to the zero-length string.
 >	A switch is identified by looking for the character '/'
 >	Switches are extracted and stored in the symbol ARG
 >	The '/' is part of the switch
 MODIFICATION HISTORY:
	JUN-1994, Paul Hick (UCSD)


Local2UT $SMEI/ucsd/gen/for/lib/gen/local2ut.f
[Previous] [Next]
 NAME:
	Local2UT
 PURPOSE:
       Read system clock, including fraction of day, convert to day of year, 
       and calculate the day of year in Universal Time (Greenwich).
 CATEGORY:
	Time calculation
 CALLING SEQUENCE:
	subroutine Local2UT(off,yr,doy)
 INPUTS:
       off	integer		offset time (in hours) from Greenwich
				(i.e. UT-local time)
 OUTPUTS:
	yr	integer		year; the year xxxBC should be entered as -xxx+1
       doy	real		day of year + fraction + offset from Greenwich
 CALLS: ***
	Time2Day, Time2Local2UT, Time2YDoy
 CALLED BY:
	SetGrid, ipsd, ipsdt
 RESTRICTIONS:
	Works only on a VAX
 PROCEDURE:
	The specified offset (in hours) is added to the obtain the doy of year
	in UT (with the time of day specified as a fraction).
 MODIFICATION HISTORY:
	Kari Winfield (UCSD)


LocateTag $SMEI/ucsd/gen/for/lib/str/locatetag.f
[Previous] [Next]
 NAME:
	LocateTag
 PURPOSE:
	Locate a tag (substring) from a list of tags (nternal use only)
 CATEGORY:
	Strings: tag manipulation
 CALLING SEQUENCE:
	function LocateTag(cSep,LS,cTags,LT,cTag)
 INPUTS:
	cSep		character	character used as separater (usually comma)
	LS		integer		only the part cTags(:LS) is searched
	cTags		character*(*)	list of tags, separated by the cSep character
	LT		integer		only the part cTag(:LT) is used
	cTag		character*(*)	tag (substring) to be removed
 OUTPUTS:
	LocateTag	integer		position of cTag in cTags
 CALLED BY:
	RemoveTag, ReplaceTag, SwitchTag
 SEE ALSO:
	RemoveTag, ReplaceTag, SwitchTag
 PROCEDURE:
       On the VMS Fortran compiler this is a no-brainer:
		LocateTag = index(cSep//cTags(:LS)//cSep,cSep//cTag(:LT)//cSep)
       This may not work on other compilers, since it involves the
       concatenation of variable length strings. A kludgy alternative is
	used here to accomplish the same.
 MODIFICATION HISTORY:
	NOV-1994, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	JUN-1995, Paul Hick (UCSD; pphick@ucsd.edu), added SwitchTag


LocFirst $SMEI/ucsd/gen/for/lib/str/locfirst.f
[Previous] [Next]
 NAME:
	LocFirst
 PURPOSE:
	Find the first occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocFirst(cFnd,cStr)
 INPUTS:
	cFnd	character*(*)	string to be searched for
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first occurrence, or
				0 if cFnd not found
 CALLED BY:
	DailyIPS_UCSD [1], DailyIPS_UCSD [2], Dbl2Str, FileSelection, Flt2Str
	ForeignArgFind, ForeignArgSet, ForeignFile, LocFirst0, LocFirstLen, Pandora
	ParseRepair, Peep, SD, SD_SCAN, Time2Time, WR2DARR, XCvarFormat, bOSFind, bOSFindClose
	dailyips [1], dailyips [2], iFileStructure, iGetDirectoryFragment, iGetFileSpec
	iGetParentDirectory, iGetTopDirectory, iSetFileSpec, ipsg2, ipsg2s, ipsg2t, mkenv
	rice, smei_cal_group, sprint
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocFirst will return 0 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LocFirst0 $SMEI/ucsd/gen/for/lib/str/locfirst0.f
[Previous] [Next]
 NAME:
	LocFirst0
 PURPOSE:
	Find the first occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocFirst0(L1,cFnd,L2,cStr)
 INPUTS:
	L1	integer		only cFnd(:L1) is searched for
	cFnd	character*(*)	string to be searched for
	L2	integer		only cStr(:L2) is searched
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first/last occurrence, or
				0 if cFnd not found
 CALLS: ***
	LocFirst
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocFirst0 will return 0 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LocFirstLen $SMEI/ucsd/gen/for/lib/str/locfirstlen.f
[Previous] [Next]
 NAME:
	LocFirstLen
 PURPOSE:
	Find the first occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocFirstLen(cFnd,cStr)
 INPUTS:
	cFnd	character*(*)	string to be searched for
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first/last occurrence, or
				len(cStr)+1 if cFnd not found
 CALLS: ***
	LocFirst
 CALLED BY:
	AskLimit, AskWhatEntry, AskWhatPrmpt, FileSelection, ForeignArg, ForeignArgs
	ForeignI2ArgN, ForeignI4ArgN, ForeignInput, ForeignR4ArgN, ForeignR8ArgN
	ForeignStrArg, SD, SD_SCAN, SD_TREE, Say, WR2DARR, dailyips [1], dailyips [2], iSearch
	iTopFragment, rice, smei_cal_group
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocFirstLen will return len(cStr)+1 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LocLast $SMEI/ucsd/gen/for/lib/str/loclast.f
[Previous] [Next]
 NAME:
	LocLast
 PURPOSE:
	Find the last occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocLast(cFnd,cStr)
 INPUTS:
	cFnd	character*(*)	string to be searched for
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first/last occurrence, or
				0 if cFnd not found
 CALLED BY:
	DailyIPS_UCSD [1], DailyIPS_UCSD [2], LocLast0, LocLastLen, SD, SD_SCAN, bOSFind
	bOSFindClose, bValidFragment, iFileStructure, iGetDirectoryFragment
	iGetFileSpec, iGetParentDirectory, iGetTopDirectory, iLastFragment
	iParentFragment, iSetFileSpec
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocLast will return 0 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LocLast0 $SMEI/ucsd/gen/for/lib/str/loclast0.f
[Previous] [Next]
 NAME:
	LocLast0
 PURPOSE:
	Find the last occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocLast0(L1,cFnd,L2,cStr)
 INPUTS:
	L1	integer		only cFnd(:L1) is searched for
	cFnd	character*(*)	string to be searched for
	L2	integer		only cStr(:L2) is searched
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first/last occurrence, or
				0 if cFnd(:L1)  not found
 CALLS: ***
	LocLast
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocLast0 will return 0 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LocLastLen $SMEI/ucsd/gen/for/lib/str/loclastlen.f
[Previous] [Next]
 NAME:
	LocLastLen
 PURPOSE:
	Find the first occurrence of string cFnd in string cStr
 CALLING SEQUENCE:
	function LocLastLen(cFnd,cStr)
 INPUTS:
	cFnd	character*(*)	string to be searched for
	cStr	character*(*)	string to be searched
 OUTPUTS:
	L	integer		position of first/last occurrence, or
				0 if cFnd not found
 CALLS: ***
	LocLast
 PROCEDURE:
 >	The index function has the quirky property that it returns 1 when
	searching for a zero-length string, i.e.
	I = index('abcd',str(:0))  will set I = 1.
	LocLastLen returns len(cStr)+1 instead.
 MODIFICATION HISTORY:
	JUL-1995, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LogModFile $SMEI/ucsd/gen/for/os/logmod.f
[Previous] [Next]
 NAME:
	LogModFile
 CALLING SEQUENCE:
	function LogModFile(iAct,cType0,cNameIn,cDef0)
 INPUTS:
	iAct		integer		1: set logical/symbol
					2: get logical/symbol
					3: delete logical/symbol
	cType0		character*(*)	'LOG': manipulate logicals
					'SYM': manipulate symbols
	cNameIn		character*(*)	name of logical/symbol

	cDef0		character*(*)	(iAct=1 only) value of logical/symbol
 OUTPUTS:
	LogModFile	integer		0: failure
					1: success
	cDef0		character*(*)   (iAct=2 only) value of logical/symbol
 CALLED BY:
	iDeleteLogical [2], iDeleteSymbol [2], iGetLogical [2], iGetSymbol [2]
	iSetLogical [2], iSetSymbol [2]
 INCLUDE:
	include		'dirspec.h'
 CALLS: ***
	TimeOut, bGetLun, iFreeLun, iListAllLun, iOSDeleteFile, iOSRenameFile, itrim
 PROCEDURE:
 >	Should not be called directly (used internally only by functions for
	manipulating logicals and symbols).
 >	LogModFile should stay as simple as possible. In particular, do not use calls
	to Say or bOpenFile, since this would create recursion (since they
	in turn call LogModFile through calls to iSetSymbol etc.)

 >	On VMS there are system calls to manipulate logicals and symbols. This setup
	maintains a set of 'logicals' and 'symbols' in a plain ascii file in the user
	home directory. This addresses one of the main portability issues we ran into
	when moving programs to Windows, Unix and Linux.
 >	VMS logicals are functionally equivalent to environment variables in Windows
	and Linux (typically they refer to directories).
	VMS symbols are loosely equivalent to aliases in Linux.
 DEPENDENCY TREE:
	itrim
	LogModFile
		itrim
		bGetLun
			iGetLun
		iFreeLun
		iOSRenameFile *(system call)
		iOSDeleteFile *(system call)
 MODIFICATION HISTORY:
	???-????, Paul Hick (UCSD/CASS)
	SEP-2007, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Now uses TimeOut to pause program for 1 second


LOSClean $SMEI/for/lib/losclean.f
[Previous] [Next]
 NAME:
	LOSClean
 PURPOSE:
	Remove lines of sight flagged by LOSReach (these los fall partially outside
	the range [XCbeg,XCend]
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSClean(I__VD,bGCamb,NBS,iXPG,iYPG,iMJDG,	IYRF,IREC,
     &		IYRS,DOYS,DIST,XLS,XLL,XDL,XCE,XE,XC,YL,OBS,PPlos)
 INPUTS:
	I__VD		integer		TOM__V (velocity data ) or TOM__G (g-level data)
	bGCamb		integer		.TRUE. for Cambridge data (otherwise .FALSE.)
					(used only if I__VD = TOM__G)
	NBS   (NL)	integer		=0: line of sight is removed
					=1: line of sight is retained
	iXPG  (NL)	integer
	iYPG  (NL)	integer
	iMJDG (NL)	integer

	IYRF  (NL)	integer
	IREC  (NL)	integer

	IYRS  (NL)	integer 	Year and ..
	DOYS  (NL)	real		Day of year (incl. fraction for time of day) of observation
	DIST  (NL)	real		Sun-Earth distance at time of obs.
	XLS   (NL)	real		Geocentric ecliptic longitude of Sun
	XLL   (NL)	real		Geocentric ecliptic longitude diff.lng(los)-lng(Sun)
	XDL   (NL)	real		Geocentric ecliptic latitude los
	XCE   (NL)	real		Carrington variable of sub-Earth point
	XE    (NL)	real		Los elongation (deg) (>0: East of Sun; <0: West of Sun)
	XC    (NL)	real		Carrington variable of point-P traced back to source
					surface at speed VOBS
	YL    (NL)	real		Heliographic latitude of point-P (deg)
	OBS   (NL)	real		Observed IPS velocities

	PPlos(4,NLOS,NL)real		Lng/lat/rad/time of points on los
 OUTPUTS:
	NBS   (NL)	integer		NBS(i),i=1,NL all set to 1

	The remaining NL lines of sight are stored in the first NL positions for all arrays.
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 SIDE EFFECTS:
	The t3d entry for NL is updated.
 CALLS: ***
	ArrR4Copy, Int2Str, Say, Str2Str, T3D_iget, T3D_iset
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_index.h'
	include		't3d_loc_fnc.h'
 PROCEDURE:
 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LOSIntegralG $SMEI/for/lib/losintegralg.f
[Previous] [Next]
 NAME:
	LOSIntegralG
 PURPOSE:
	Calculate model line of sight g-levels
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSIntegralG(I__VD,XCbegMAT,XCendMAT,G3D,M2Mean,PPlos,WWlos,G2MDL,GWT,G2)
 INPUTS:
	I__VD			integer		TOM__V (IPS velocities) or TOM__G (g-levels)
	XCbegMAT(nTim)		real		start Carrington variable (corresponding to I=nLng)
	XCendMAT(nTim)		real		end Carrington variable (corresponding to I=1)
	G3D(nLng,nLat,nRad,nTim)real		g^2
	M2Mean(NL)		real		square of mean scintillation index (from LOSWeights)
	PPlos(4,NLOS,NL)	real		Lng/lat/rad/time of points on los
	WWlos(NLOS,NL)		real		integration weight for each los segment (from LOSWeights)
	G2   (NLOS,NL)		real		scratch array
 OUTPUTS:
	G2MDL(NL)		real		model G-levels
	GWT  (NLOS,NL)		real		weights used in BuildSourceSurface to combine
						los segments projected into the same bin
 CALLS: ***
	ArrR4DivideByArrR4, ArrR4DivideByConstant, ArrR4TimesArrR4, ArrR4Total
	GetLOSValue, T3D_iget
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_loc_fnc.h'
 PROCEDURE:
	Scintillation index	m^2 = Int[W(z) dz] 
	Weighting function	W(z) = (Delta N_e(z))^2 int dq sin^2(frac{q^2 lambda z}{4 pi})
					exp(-frac{theta_o^2 q^2 z^2}{2}) q^{-3}

	bInclG controls the calculation of GWT, the weights passed to BuildSourceSurface.
	bInclG=.TRUE. : GWT = WWlos*g^2/Integral(WWlos*g^2)
	bInclG=.FALSE.: GWT = WWlos    /Integral(WWlos    )
	In both cases the sum of the weights along a line of sight adds up to 1.
 	(Remember that M2Mean = Integral(WWlos))
 MODIFICATION HISTORY:
	NOV-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LOSIntegralV $SMEI/for/lib/losintegralv.f
[Previous] [Next]
 NAME:
	LOSIntegralV
 PURPOSE:
	Calculate model line of sight values for IPS velocities
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSIntegralV(I__VD,XCbegMAT,XCendMAT,V3D,G3D,PPlos,WWlos,VPlos,VMDL,VWT,VSUM,VVG2)
 INPUTS:
	I__VD			integer	TOM__V (IPS velocities) or TOM__G (g-levels)
	XCbegMAT(nTim)		real	start Carrington variable
	XCendMAT(nTim)		real	end Carrington variable
	V3D(nLng,nLat,nRad,nTim)real	velocities
	G3D(nLng,nLat,nRad,nTim)real	g^2
	PPlos(4,NLOS,NL)	real	Lng/lat/rad/time of points on los
	WWlos(NLOS,NL)		real	integration weight for each los segment (from LOSWeights)
	VSUM (     NL)		real	scratch array
	VVG2 (NLOS,NL,2)	real	scratch array
 OUTPUTS:
	VMDL(NL)		real	model IPS V values
	VWT (NLOS,NL)		real	weights used in BuildSourceSurface to combine
					los segments projected into the same bin
 CALLS: ***
	ArrR4DivideByArrR4, ArrR4DivideByConstant, ArrR4TimesArrR4, ArrR4Total
	GetLOSValue, T3D_iget
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
 PROCEDURE:
	bInclV controls the calculation of VWT, the weights passed to BuildSourceSurface.
	bInclV=.TRUE. : VWT = WWlos*g^2*Vperp/Integral(WWlos*g^2*Vperp)
	bInclV=.FALSE.: VWT = WWlos*g^2/Integral(WWlos*g^2)
	In both cases the sum of the weights along the line of sight is 1.
 MODIFICATION HISTORY:
	NOV-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LOSPosition $SMEI/for/lib/losposition.f
[Previous] [Next]
 NAME:
	LOSPosition
 PURPOSE:
	Calculates heliographic coordinates for all NLOS line of sight segments (of length dLOS)
	for a collection of NL lines of sight.
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSPosition(I__VD,IYRS,DOYS,DIST,XLS,XCE,XLL,XDL,PPlos,VPlos)
 INPUTS:
	I__VD		integer		TOM__V (IPS velocities) or TOM__G (g-levels)
	IYRS(NL)	integer		Year of observation
	DOYS(NL)	real		Day of year (and fraction) of observation
	DIST(NL)	real		Sun-Earth distance (AU)
	XLS (NL)	real		Geocentric ecliptic longitude of Sun (deg)
	XCE (NL)	real		Carrington variable of sub-Earth point
	XLL (NL)	real		Geocentric ecliptic longitude difference lng(los)-lng(Sun) (deg)
	XDL (NL)	real		Geocentric ecliptic latitude of los (deg)
 OUTPUTS:
	PPlos(4,NLOS,NL)real		Lng/lat/rad/time of point on LOS
					time = XCE with a negative correction for the light travel time from
					point on LOS to observer
	VPlos(NLOS,NL)	real		sin(Chi)=Vperp/Vrad (used for velocity IPS to calculate
					the perpendicular velocity component from the (radial) velocity
 CALLS: ***
	ECLIPTIC_HELIOGRAPHIC, POINT_ON_LOS, T3D_get, T3D_iget, XMAP_OBS_POS, sind
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		'phys.h'
	include		'sun.h'
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_index.h'
	include		't3d_loc_fnc.h'
 PROCEDURE:
 >	XClos is on the same scale as XCE.
 >	The output coordenates refer to the center of the segments
 >	Note that no attempt is made to keep the heliographic coordinates inside a fixed
	range. This is taken care of in LOSProjection.
 MODIFICATION HISTORY:
	FEB-1999, P. Hick (UCSD/CASS), split original in two functions: LOSPosition and LOSProjection
	JUL-2001, P. Hick (UCSD/CASS; pphick@ucsd.edu), added TTlos argument


LOSProjection $SMEI/for/lib/losprojection.f
[Previous] [Next]
 NAME:
	LOSProjection
 PURPOSE:
	Determines heliographic coordinates of los segments after projection
	to the source surface
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSProjection(I__VD,XCbegMAT,XCendMAT,XC3D,PPlos,PPprj)
 INPUTS:
	XCbegMAT(nTim)		real		start Carrington variable
	XCendMAT(nTim)		real		end Carrington variable
	XC3D(3,nLng,nLat,nRad,nTim)
				real 		Lng/lat/time shifts to source surface
						(set by SW_Model_Kinematic)
	PPlos(4,NLOS,NL)	real		Lng/lat/rad/time of points on los
 OUTPUTS:
	PPprj(3,NLOS,NL)	real		Lng/lat/time of origin at source
						surface RR for points on LOS.
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_index.h'
	include		't3d_loc_fnc.h'
 CALLS: ***
	BadR4, GetLOSValue, T3D_iget
 PROCEDURE:
 >	All longitudes are in Carrington variables (with an offset NCoffset
	subtracted)
 >	PPlos is output from LOSPosition.
	The segment positions have been checked by LOSReach, i.e.
		All latitudes and radial distances lie inside the reconstruction volume.
		If iand(MODE,TOM__MOD) = 0 the same is true for the longitudes
		If iand(MODE,TOM__MOD) > 0 the longitudes values may lie outside
			[XCbeg,XCend] but they will be mapped inside this range by GetLOSValue.
 >	Effectively all segments lie inside the volume covered by XC3D, and since
	XC3D is output by SW_Model_Kinematic without any bad values in it, interpolation
	on XC3D at positions PPlos will always give a good value.
	This is added to PPlos to obtain the projected PPprj at the source surface.
 >	The resulting projected longitudes may lie outside the range [XCbeg,XCend].
	This will be dealt with in BuildSourceSurface (the only routine that uses PPprj)

 >	When bMHD = iand(MODE,TOM__MHD) .ne. 0 then a general calculation is done
	without making any assumptions about the shifts in longitude, latitude and time.
	When the kinematic model is used then the latitude shifts is assumed zero, and
	the time shift is assumed equal to the longitude shift. The general calculation
	will work for the kinematic model but is much slower.
 MODIFICATION HISTORY:
	FEB-1999, P. Hick (UCSD/CASS), split original into two functions:
		LOSPosition and LOSProjection
	AUG-2001, P. Hick (UCSD/CASS; pphick@ucsd.edu), generalized for MHD model


LOSReach $SMEI/for/lib/losreach.f
[Previous] [Next]
 NAME:
	LOSReach
 PURPOSE:
	Does a sanity check on the los segment locations output by LOSProjection
 CATEGORY:
	Data processing
 CALLING SEQUENCE:
	subroutine LOSReach(I__VD,XCbegMAT,XCendMAT,PPlos,NBS)
 INPUTS:
	MODE		integer		= iand(MODE,TOM__MOD) > 0: remap XC using mod(XCend-XCbeg)
					= iand(MODE,TOM__MOD) = 0: no remapping
	NCoff		integer		Carrington rotation offset to be applied to
					XCbeg, XCend and XClos

	TT		real		start time as Carrington variable (- NCoff)
	dTT		real		time resolution as Carrington variable
					(if nTim = 1 then dTT should be set to zero)
	RR		real		heliocentric distance of source surface (AU) 
	dRR		real		radial distance resolutions (AU)

	nLng		integer		# longitudes
	nLat		integer		# latitudes
	nRad		integer		# heliocentric distances
	nTim

	XCbegMAT(nTim)	real		start Carrington variable
	XCendMAT(nTim)	real		end Carrington variable

	NL		integer		# IPS G-level observations
	NLOS		integer		# segments of length dLOS along los
	PPlos(4,NLOS,NL)real		Lng/lat/rad/time of point on los
 OUTPUTS:
	NBS(NL)		integer		iand(MODE,TOM__MOD) > 0: all set to 1
					iand(MODE,TOM__MOD) = 0: set to 1 if whole line of sight
					insided range [XCbeg,XCend]; otherwise set to 0.
					(los with NBS=0 will be discarded later by LOSClean)
	iMap		integer		Lowest heliocentric distance index (<=nRad) above
					all los segments
 CALLS: ***
	ArrI4Constant, ArrR4Total, Say, T3D_get_grid, T3D_iget, T3D_iset, cFlt2Str, cInt2Str
	iArrI4Total, iwhitespace, pInfR4
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_index.h'
	include		't3d_grid_fnc.h'
	include		't3d_loc_fnc.h'
 PROCEDURE:
 >	XClos and XCprj are on the same scale as XCbeg and XCend.
 >	XClos, XLlos, RRlos are output from LOSPosition.
 >	iand(MODE,TOM__MOD) > 0:
		Program is terminated if XLlos or RRlos values lie outside the volume
		covered by the reconstruction. XClos is allowed to fall outside [XCbeg,XCend]
		(these will be mapped inside this range by GetLOSValue, when necessary).
 >	iand(MODE,TOM__MOD) = 0:
		Program is terminated if XClos, XLlos or RRlos values lie outside the volume.
 >	Effectively LOSReach makes sure that all segments lie inside the reconstruction volume
 >	Note that segments can still end up outside [XCbeg,XCend] after traceback to the
	source surface.
 MODIFICATION HISTORY:
	SEP-1999, P. Hick (UCSD/CASS; pphick@ucsd.edu)


LOSSanityCheck $SMEI/for/lib/lossanitycheck.f
[Previous] [Next]
 NAME:
	LOSSanityCheck
 PURPOSE:
	Does a couple of sanity checks before starting a tomgraphy run
 CALLING SEQUENCE:
	subroutine LOSSanityCheck(bVcon,bGcon)
 INPUTS:
	bVcon		logical		.TRUE. when velocity deconvolution is requested
	bGcon		logical		.TRUE. when g-level deconvolution is requested
 CALLS: ***
	Say, T3D_iget
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
 PROCEDURE:
	Currently it is only checked whether IPS data (velocity or g-level) are
	available when a deconvolution (of velocity or g-level) is requested.
 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


LOSTweak $SMEI/for/lib/lostweak.f
[Previous] [Next]
 NAME:
	LOSTweak
 PURPOSE:
	Determines the corrections to be applied to the model line of
	sight observations based on differences with the actual observations
	[g = m/<m> ==> dm = <m> dg]
 CATEGORY:
 CALLING SEQUENCE:
	subroutine LOSTweak(I__VD,XOBS,XMDL,NBAD,FIX,FIXMEAN,FIXSTDV)
 INPUTS:
	I__VD		integer	TOM__V: Fix V model
				TOM__G: Fix G model
	XOBS(NL)	real	Observed values (V, g^2)
	XMDL(NL)	real	Model values	(V, g^2)
 OUTPUTS:
	FIX(NL)		real	Ratio of observed to model values
				FIX(I) =  XOBS(I)/XMDL(I)
	FIXMEAN		real	= 1.
	FIXSTDV		real	sqrt( (1/NL)*Sum[I]{ ( (XOBS(I)-XMDL(I))/XMDL(I) )^2 } =
				sqrt( (1/NL)*Sum[I]{   (XOBS(I)/XMDL(I)-1.)^2 } =
				sqrt( (1/NL)*Sum[I]{   (FIX(I)-1.)^2 }
				something like a standard deviation from an assumed mean of one.
 CALLS: ***
	ArrR4GetMinMax, BadR4, Flt2Str, Say, Str2Str, T3D_iget
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 INCLUDE:
	include		't3d_param.h'
	include		't3d_array.h'
 PROCEDURE:
	MODE		integer	= iand(MODE,TOM__DIFF)= 0: los ratios
				= iand(MODE,TOM__DIFF)> 0: los differences
 MODIFICATION HISTORY:
	NOV-1995, B. Jackson (STEL,UCSD)
	AUG-2001, Paul Hick (UCSD/CASS; pphick@ucsd.edu); introduced T3D_iget calls


LOSWeights $SMEI/for/lib/losweights.f
[Previous] [Next]
 NAME:
	LOSWeights
 PURPOSE:
	Determine weights for set of points along a line of sight 
 CATEGORY:
	Tomography
 CALLING SEQUENCE:
	subroutine LOSWeights(I__VD,IM,XE,XR,PPlos,WWlos,M2Mean)
 INPUTS:
	IM		integer		Mode of operation
		1 = Nagoya	- 327 MHz
		2 = Cambridge	- 81.5 MHz
		3 = UCSD	- 72.8 MHz
		4 = Thomson scattering U weights
		5 = Thomson scattering B weights
		6 = Thomson scattering V weights
	XE(NL)		real		IPS line of sight elongations (deg)
	XR(NL)		real		Observer-Sun distance (AU)
	PPlos(4,NLOS,NL)
 OUTPUTS:
	WWlos(NLOS,NL)	real		Weights at each pos. along the los
 CALLS: ***
	ArrR4Copy, ArrR4Total, ElSunDistance, IPSBase, IPSConst, Say, T3D_get, T3D_iget
	ThomsonBase, ThomsonUBVConst, cFlt2Str
 CALLED BY:
	ipsg2, ipsg2s, ipsg2t
 SEE ALSO:
	MkLOSWeights
 INCLUDE:
	include		'sun.h'
	include		't3d_param.h'
	include		't3d_array.h'
	include		't3d_index.h'
	include		't3d_loc_fnc.h'
 RESTRICTIONS:
	For the IPS weights a fudge is used to speed up calculations.
	The average Sun-Earth distance is used for all lines of sight. As a result
	only one line of sight needs to be calculated by IPSBase.
 PROCEDURE:
	If the radial power index PWR is unequal 2, then an additional weight factor is
	included. The extra term comes from the radial dependence of the density fluctations
	in the los integral. delta(n)^2 ~ r^[-2*(2-PWR)]
 MODIFICATION HISTORY:
	NOV, 1995 B. Jackson (STEL, UCSD)
	JAN-2000, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	Added extra weight factor to cover radial dependence of the los weight
	factors. Also added the calculation of the mean scintillation index.
	(pulling this out of the iteration loop provides a significant gain in speed).


lowercase $SMEI/ucsd/gen/for/lib/str/lowercase.f
[Previous] [Next]
 NAME:
	lowercase
 PURPOSE:
	Convert string to lowercase
 CATEGORY:
	String manipulation
 CALLING SEQUENCE:
	subroutine lowercase(C)
 INPUTS:
	C		character*(*)	string to be processed
 OUTPUTS:
	C		character*(*)	modified string
 CALLED BY:
	ForeignFile, HERDISK, Peep, mkenv, rice, smei_foreign
 SEE ALSO:
	bCompareStr, icompress, itrim, iwhitespace, uppercase
 PROCEDURE:
	Each character in the string is converted separately.
	The intrinsic FORTRAN functions ICHAR is used to find the ASCII code
	for the character. For uppercase characters (ASCII code 65-90) 32 is added
	to the ASCII code. The FORTRAN function CHAR is used to convert the
	corrected code back to an character.
 MODIFICATION HISTORY:
	JAN-1992, Paul Hick (UCSD)