PA_Pole $SMEI/ucsd/sat/idl/toolbox/sun/pa_pole.pro
[Previous] [Next]
 NAME:
	PA_Pole
 PURPOSE:
	Calculate the position angle of the solar north pole
 CATEGORY:
	Astronomy: celestial physics
 CALLING SEQUENCE:
	PA = PA_POLE(T, lngsun=LngSun)
 INPUTS:
	T	array; type: time structure
		    times (UT)
	lngsun=LngSun
		array; type: float
		    ecliptic longitude of Sun as viewed from observer
 OPTIONAL INPUTS:
	/equatorial	if set, the return value is relative to equatorial
			north (default is ecliptic north)
	/southpole	if set, return values for solar south pole
			(default: solar north pole)
	/degrees	if set, all angles are in degrees (default is radians)
 OUTPUTS:
	PA_POLE array; type: float
		    position angle
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, TimeGet, TimeUnit, ToRadians
 PROCEDURE:
	For given time T and ecliptic longitude of the Sun (as seen
	from an observer in the ecliptic plane) the position angle
	of the solar pole is calculated, either relative to ecliptic or to
	equatiorial North.
	See Spherical Astronomy pp. 430-433 by Green, Robin M., Cambridge UP
	(1985) (The position angle is measured counterclockwise, i.e. toward
	the east, from North)
 MODIFICATION HISTORY:
	JUL-1992, Tom Davidson (UCSD/CASS)
	SEP-1992, Paul Hick (UCSD/CASS), converted from F77 to IDL
	FEB-1998, Paul Hick (UCSD/CASSu)
	    added keywords /degrees and /southpole
	NOV-1999; Paul Hick (UCSD/CASS, pphick@ucsd.edu); switched to using
	    time structures instead of yr,doy


packet_size_graphs $SMEI/user/pphick/idl/network/packet_size_graphs.pro
[Previous] [Next]
 NAME:
	packet_size_graphs
 PURPOSE:
 CALLING SEQUENCE:
	PRO packet_size_graphs, filename, $
	    file    = file	, $
	    zbuffer = zbuffer	, $
	    title   = title	, $
	    noipv6  = noipv6	, $
	    charsize= charsize	, $
	    thick   = thick	, $
	    xysize  = xysize	, $
	    silent  = silent	, $
	    _extra  = _extra
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	GetFileSpec, InitVar, IsType, PlotBars, PlotCurves, get_page, pkt_read, set_page


packet_size_one_graph $SMEI/user/pphick/idl/network/packet_size_one_graph.pro
[Previous] [Next]
 NAME:
	packet_size_one_graph
 CALLING SEQUENCE:
	PRO packet_size_one_graph, pkt_size, pkt_count, $
	    label	    = label	, $
	    color	    = color	, $
	    linestyle	    = linestyle , $
	    oplotx	    = oplotx	, $
	    _extra	    = _extra
 INCLUDE:
	@compile_opt.pro
COMMON:
common packet_size_common
x
y
 CALLS: ***
	InitVar, PLOTBAR, gridgen


packet_size_update $SMEI/user/pphick/idl/network/packet_size_update.pro
[Previous] [Next]
 NAME:
	packet_size_update
 PURPOSE:
 CALLING SEQUENCE:
	PRO packet_size_update, silent=silent
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	InitVar, IsType, PACKET_SIZE_GRAPH, TimeGet, TimeSet, get_page, pkt_read, set_page


parseooty $SMEI/user/jclover/from_ztemp/parseooty.pro
[Previous] [Next]
 NAME:
	parseooty
 CALLING SEQUENCE:
	PRO parseooty
 CALLS: ***
	STRSPLIT, TimeOp, TimeSet, TimeString


pcursor $SMEI/ucsd/sat/idl/util/pcursor.pro
[Previous] [Next]
 NAME:
	pcursor
 PURPOSE:
	Kludging the IDL CURSOR procedure
 CALLING SEQUENCE:
	pcursor, xp, yp [, /device, /normal, /data, /down]
 INPUTS:
	None
 OUTPUTS:
	xp, yp	    coordinates of spin-hair cursor
	!err	    = 1/2/4 when left/middle/right button is pushed
	perror	    !err value returned by CURSOR procedure
	kludge	    if !d.name eq 'TEK' a blank print statement is inserted
		    after the call to cursor
 INCLUDE:
	@compile_opt.pro    ; On error, return to caller
 CALLED BY:
	edit_smei, editsmei, fancy
 COMMON BLOCKS:
	common	save_pcursor, ginchars
 CALLS: ***
	IsWindowSystem
 PROCEDURE:
 >>	the KLUDGE keyword is required only for EMUTEK at the moment. Without
	the extra print statement the first call to CURSOR will work, but
	all subsequent calls will make EMUTEK get stuck in GIN mode. The
	reason is unclear.

 >>	When using a mouse to select a screen location, the mouse buttons
	should return 1,2 and 4 in the !ERR system variable for left, middle
	and right mouse button (if the mouse has only two buttons use 1 and 2).
	The keys 1,2,3 or a,b,c or A,B,C or CTRL-A,CTRL-B,CTRL-C can be used
	to mimick mouse action, provided the CURSOR procedure puts the ASCII
	decimal equivalent of the corresponding key in the !ERR variable. If
	you get funny characters on the screen and/or you have to press one or
	more keys to return to the IDL prompt, there may be problems with the
	type-ahead buffer (i.e. CURSOR puts more/less characters in the type
	ahead buffer than IDL reads out of it before continuing). Set
	DEVICE,gin_chars=6 and try again.

	X-windows (!d.name = 'X'):
	    Should work without any problems
	HDS3200 terminal (!d.name = 'TEK'):
	    The mouse button keys should be user defined as <SOH>, <STX>
	    and <EOT> for left, middle and right button respectively (the
	    corresponding keyboard strokes are CTRL A, CTRL B and CTRL D).
	    The error codes returned when pushing a button are the decimal
	    equivalent of the first character of the user definition, which
	    for the settings given above results 1,2 and 4 for left, middle
	    and right button respectively. The IDL CURSOR procedure places
	    the user definition of the button in the type-ahead buffer
	    (one character in this case).
	VT240 (!d.name = 'REGIS'):
	    It worked the last time I tried
 MODIFICATION HISTORY:
	FEB-91, Paul Hick (ARC)


physics_constant $SMEI/ucsd/gen/idl/toolbox/physics/physics_constant.pro
[Previous] [Next]
 NAME:
	physics_constant
 PURPOSE:
	Gets value of fundamental physics constant
 CATEGORY:
	gen/idl/toolbox
 CALLING SEQUENCE:
    FUNCTION physics_constant, char_string, $
	    unit=unit, uncertainty=uncertainty, name=name, $
	    exponent=exponent
 INPUTS:
	char_string	scalar; type: string
			    string descriptof for constant
			    e.g. 'speed of light'
 OPTIONAL INPUT PARAMETERS:
	/exponent	passes to flt_string
 OUTPUTS:
	value		scalar or array[2]; type: double
			    value of constant
 OPTIONAL OUTPUT PARAMETERS:
	unit=unit	scalar; type: string
			    unit of 'value' (mks units are used)
	uncertainty=uncertainty
			scalar; type: double
			    uncertainty in 'value'
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	BadValue, GetFileSpec, flt_string, txt_read, who_am_i
 PROCEDURE:
	Uses list of physical constants from
	    http://physics.nist.gov/cuu/Constants/Table/allascii.txt
	renamed to
	    physics_constant.txt in the same directory as this function.
 MODIFICATION HISTORY:
	MAR-2007, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


pkt_read $SMEI/user/pphick/idl/network/pkt_read.pro
[Previous] [Next]
 NAME:
	pkt_read
 PURPOSE:
	Read ASCII files with packet size distribution
 CALLING SEQUENCE:
	FUNCTION pkt_read, filenames	, $
	    ipv4_total_count	= ipv4_total_count  , $
	    ipv6_native_count	= ipv6_native_count , $
	    ipv6_tunnel_count	= ipv6_tunnel_count , $
	    protocol		= protocol	    , $
	    max_packet_size	= max_packet_size   , $
	    truncate		= truncate
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	InitVar, IsType, STRSPLIT, WhatIs, flt_read
 CALLED BY:
	packet_size_graphs, packet_size_update
 MODIFICATION HISTORY:


plot3darc $SMEI/ucsd/sat/idl/toolbox/tricks/plot3darc.pro
[Previous] [Next]
 NAME:
	plot3darc
 PURPOSE:
	Plot an arc in a 3d geometry (with optional label)
 CATEGORY:
	Tricks
 CALLING SEQUENCE:
	plot3darc, center, nn1, nn2 [, arcbegin, arclength, degrees=degrees,	$
	    color=color, tiplen=tiplen, tipwid=tipwid,	    $
	    labeltext=labeltext, labelradius=labelradius, labeloffset=labeloffset]
 INPUTS:
	center	    array[3]; type: int or float
			Cartesian coordinates of center of arc
	nn1, nn2    array[3]; type: int or float
			Cartesian coordinates defining plane in which arc is to be drawn
	    The arc is drawn in one of two ways:
	    1.	if arcbegin and arclength both specified:
		nn1 is intepreted as 'x-axis', nn2 as y-axis; the arc is drawn by connecting points
		    center+(nn1*cos(angle)+nn2*sin(angle)) where angle covers [arcbegin,arcbegin+arclength]
		    In this case n1 and n2 usually will be two perpendicular vectors
	    2.	if either arcbegin or arclength not specified
		    nn1 and nn2 are connected by arc
 OPTIONAL INPUT PARAMETERS:
	arcbegin    scalar; type: int or float
			phase angle for the starting point of the arc in the [nn1,nn2] plane
	arclength   scalar; type: int or float
			length of the arc
	/degrees    if set, arcbegin and arclength are assumed to be in radians

	color=color if set, the area between the center and the arc is shaded with the specfied color

	tiplen=tiplen		keyword passed to arrow3d
	tipwid=tipwid		keyword passed to arrow3d
		    if one of these keywords is set the end point of the arc (at nn2) receives an
		    3D arrow point

	labeltext=labeltext
		    scalar; type: string
			string to plotted somewhere near the arc. The following three keywords are only used
			if labeltext is provided:
	labelradius=labelradius
		    scalar; type: int or float
			as a first approximation the string is plotted near the middle of the arc
			between nn1 and nn1 at a distance of labelradius times the radius of the arc.
			Usually labelradius is somewhat greater than one.
	labeloffset=labeloffset
		    array[2]; type: int or float
			adjustment to the position of labeltext in x and y data coordinates
			This is usually to manually tweak the position determined with labelradius
			(depending on the !p.t matrix the computed position can be awkward).
 OUTPUTS:
	circle=circle
		    array[3,361]; type: float
			3D-coordinates of point along arc. If this keyword is present
			then nothing is plotted.
 INCLUDE:
	@compile_opt.pro		; On error, return to caller
 CALLS: ***
	InitVar, IsType, SuperArray, ToRadians, arrow3d, gridgen, plot3dtext, vectorproduct
 CALLED BY:
	PlotSolarDisk, brachistochrone, cvplot_figures, even_light_figures, losgeometry
	miscfig, projfig, qvu_draw, smeifig, ss_map, thomsonfig, tomography_sp
 SEE ALSO:
	setup3d
 RESTRICTIONS:
	A proper !p.t matrix must be set up (e.g. with setup3d)
 PROCEDURE:
 MODIFICATION HISTORY:
	AUG-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plot3dcube $SMEI/ucsd/sat/idl/toolbox/tricks/plot3dcube.pro
[Previous] [Next]
 NAME:
	plot3dcube
 PURPOSE:
	Plot 3D cube with optional label
 CATEGORY:
 CALLING SEQUENCE:
	plot3dcube, r0, r1 [, linestyle=linestyle, thick=thick, $
	    labeltext=labeltext, labeldist=labeldist, labeloffset=labeloffset, charsize=charsize, charthick=chartick]
 INPUTS:
	r0, r1	    array[3]; type: int of float
			rectangular coordinates for begin and end point of line (in data coordinates)
 OPTIONAL INPUT PARAMETERS:
	linestyle=linestyle, thick=thick
			IDL keywords passed to plots, /t3d command for drawing line
	tiplen=tiplen, tipwid=tipwid, color=color
			keywords passed to arrow3d. If either tiplen or tipwid is set then arrow3d is called
			to add a 3D arrow point to the end of the line (at r1 side)
	labeltext=labeltext
		    scalar; type: string
			label to plotted near axis (usually near the end r1)

	There are two keywords to determine label placement:

	labeldist=labeldist
		    scalar; type: int or float
			labeldist is a distance (in data coordinates) along the line from r0 to r1 where the label
			is placed. Since this placement sometime looks messy when a strange 3D transformation
			is in effect, labeloffset
	labeloffset=labeloffset
		    array[2]; type: int or float
			adjustment to the position of labeltext in x and y data coordinates
			This is usually used to manually tweak the position determined with labeldist
			(depending on the !p.t matrix the computed position can be awkward).
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, IsType, plot3dtext
 CALLED BY:
	cvplot_figures
 PROCEDURE:
 MODIFICATION HISTORY:
	APR-2000, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plot3dline $SMEI/ucsd/sat/idl/toolbox/tricks/plot3dline.pro
[Previous] [Next]
 NAME:
	plot3dline
 PURPOSE:
	Plot line ('axis') in 3D with optional label
 CATEGORY:
	Tricks
 CALLING SEQUENCE:
	plot3dline, r0, r1 [, linestyle=linestyle, thick=thick, $
	    labeltext=labeltext, labeldist=labeldist, labeloffset=labeloffset, charsize=charsize, charthick=chartick]
 INPUTS:
	r0, r1	    array[3]; type: int or float
			rectangular coordinates for begin and end point of line (in data coordinates)
 OPTIONAL INPUT PARAMETERS:
	tiplen=tiplen, tipwid=tipwid, color=color
			keywords passed to arrow3d. If either tiplen or tipwid is set then arrow3d is called
			to add a 3D arrow point to the end of the line (at r1 side)
	labeltext=labeltext
		    scalar; type: string
			label to be plotted near axis (usually near the end r1)

	There are two keywords to determine label placement:

	labeldist=labeldist
		    scalar; type: int or float
			labeldist is a distance (in data coordinates) along the line from r0 to r1 where the label
			is placed. Since this placement sometime looks messy when a strange 3D transformation
			is in effect, labeloffset
	labeloffset=labeloffset
		    array[2]; type: int or float
			adjustment to the position of labeltext in x and y data coordinates
			This is usually used to manually tweak the position determined with labeldist
			(depending on the !p.t matrix the computed position can be awkward).
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, IsType, arrow3d, plot3dtext
 CALLED BY:
	brachistochrone, cvplot_figures, even_light_figures, losgeometry, miscfig, projfig
	qimage_fig, qvu_draw, smeifig, thomsonfig, tomography_sp
 PROCEDURE:
 MODIFICATION HISTORY:
	AUG-1999, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plot3dtext $SMEI/ucsd/sat/idl/toolbox/tricks/plot3dtext.pro
[Previous] [Next]
 NAME:
	plot3dtext
 PURPOSE:
	Plots a text string at a 3D location
 CATEGORY:
	Tricks
 CALLING SEQUENCE:
	plot3dtext, pos, labeltext, labeloffset=labeloffset
 INPUTS:
	pos	    array[3]; type: int or float
			rectangular coordinates for positioning string (in data coordinates)
	labeltext   scalar; type: string
			label to be plotted
 OPTIONAL INPUT PARAMETERS:
	labeloffset=labeloffset
		    array[2]; type: int or float
			adjustment to the position of labeltext in x and y data coordinates
			This is usually used to manually tweak the position determined with labeldist
			(depending on the !p.t matrix the computed position can be awkward).
 OUTPUTS:
	(none)
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, coord3to2
 CALLED BY:
	PlotSolarDisk, brachistochrone, cvplot_figures, even_light_figures, losgeometry
	plot3darc, plot3dcube, plot3dline, projfig, qimage_fig, smeifig
 PROCEDURE:
 MODIFICATION HISTORY:
	APR-2000, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


Plot_g_level1 $SMEI/user/tdunn/idl/plot_g_level1.pro
[Previous] [Next]
 NAME:
 Plot_g_level1

 PURPOSE:
  To plot the g-level of each radio source observed and modeled

 USAGE:
  .run ~soft/jackson/idl/Plot_g_level1.pro

 NOTE:
   Put the following file in the temp directory.
     Helios


Coded by B. Jackson (January 28, 2003)
 CALLS: ***
	FILEPATH, WRITE_BMP, WhatIs, do_file, txt_read


Plot_Helios_Br $SMEI/user/tdunn/idl/plot_helios_br.pro
[Previous] [Next]
 NAME:
	Plot_Helios_Br

 PURPOSE:
	To plot the brightness of each photometer observed and model

 USAGE:
	.run ~soft/jackson/idl/PlotHelios.pro

 NOTE:
	Put the following file in the temp directory.
     Helios


			 Coded by B. Jackson (February 20, 2002)
 CALLS: ***
	FILEPATH, WRITE_BMP, WhatIs, do_file, txt_read


plot_ipv6_fraction $SMEI/user/pphick/idl/network/plot_ipv6_fraction.pro
[Previous] [Next]
 NAME:
	plot_ipv6_fraction
 PURPOSE:
 CALLING SEQUENCE:
	pro plot_ipv6_fraction, time, total_traffic, traffic, $
	    title	= title 	, $
	    ytitle	= ytitle	, $
	    name	= name		, $
	    color	= color 	, $
	    _extra	= _extra	, $
	    silent	= silent	, $
	    show_labels = show_labels	, $
	    yrange	= yrange	, $
	    ylog	= ylog		, $
	    fit 	= fit
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	BadValue, CORRELATE, InitVar, LINFIT, PlotCurves, SuperArray, TimeGet, TimeOp, TimeScale
	TimeSet, TimeUnit, ToRadians
 CALLED BY:
	ipv6_traffic


plot_traffic $SMEI/user/pphick/idl/network/plot_traffic.pro
[Previous] [Next]
 NAME:
	plot_traffic
 PURPOSE:
 CALLING SEQUENCE:
	pro plot_traffic, time, traffic, $
	    title	= title 	, $
	    ytitle	= ytitle	, $
	    name	= name		, $
	    color	= color 	, $
	    _extra	= _extra	, $
	    silent	= silent	, $
	    show_labels = show_labels	, $
	    yrange	= yrange	, $
	    ylog	= ylog		, $
	    fit 	= fit
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	BadValue, CORRELATE, InitVar, LINFIT, PlotCurves, SuperArray, TimeGet, TimeOp, TimeScale
	TimeSet, TimeUnit, ToRadians, WhatIs
 CALLED BY:
	ipv6_traffic


Plot_velocity $SMEI/user/tdunn/idl/plot_velocity.pro
[Previous] [Next]
 NAME:
	Plot_velocity

 PURPOSE:
	To plot the g-level of each radio source observed and modeled

 USAGE:
	run ~soft/jackson/idl/Plot_velocity.pro

 NOTE:
	Put the following file in the temp directory Helios

 CALLS: ***
	FILEPATH, WRITE_BMP, WhatIs, do_file, txt_read
 MODIFICATION HISTORY:
	Coded by B. Jackson (January 28, 2003)


PlotBars $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars.pro
[Previous] [Next]
 NAME:
	PlotBars
 PURPOSE:
	Plots bar graph
 CALLING SEQUENCE:
	PRO PlotBars, xin, yin, nvalid		    , $
	    sigma	    = sigma		    , $
	    xrange	    = xrange		    , $
	    yaxis	    = yaxis		    , $
	    ynozero	    = ynozero		    , $
	    ylog	    = ylog		    , $
	    yrange	    = yrange		    , $
	    ystyle	    = ystyle		    , $
	    ycolor	    = ycolor		    , $
	    color	    = color		    , $
	    changecolor     = changecolor	    , $
	    barwidth	    = barwidth		    , $
	    barname	    = barname		    , $
	    barpos	    = barpos		    , $
	    use_min_barwidth= use_min_barwidth	    , $
	    shade	    = shade		    , $
	    hatch	    = hatch		    , $
	    cdf 	    = cdf		    , $
	    ccdf	    = ccdf		    , $
	    relative	    = relative		    , $
	    nojoin	    = nojoin		    , $
	    noline	    = noline		    , $
	    low_margin	    = low_margin	    , $
	    vertical	    = vertical		    , $
	    horizontal	    = horizontal	    , $
	    fill_sparse     = fill_sparse	    , $
	    _extra	    = _extra
 INPUTS:
	xin, yin	array[n]; one-dimensional arrays
			must have the same size
	nvalid		identifies the array elements to be plotted as:
			- an array of indices e.g. [0,1,2,7,8,9,10]
			- a boolean array[n] (containing only values 0 or 1)
			of same size as xin and yin, e.g. [1,1,1,0,0,0,0,1,1,1,1]
			if nvalid is absent, all finite function values are plotted
 OPTIONAL INPUT PARAMETERS:
	/use_min_barwidth
			use a constant bar width based on the minimum distance
			between data points.
	barwidth	scalar; type: float; default: 1
			by default, bars are drawn with no intervening space, i.e.
			the right side of one bar coincides with the left side of
			its neighbour to the right; or, if /use_min_barwidth is set,
			the default barwidth is the minimum distance between
			neighbouring data points.
			Barwidth is used as a scaling
			factor for the bar width, e.g. barwidth=0.5 will leave
			a space in between bars, equal to the width of the bars.
	barname=barname
			array[n]; type: string; default: none
			string to be plotted alongside each bar at position
			specified in barpos
	barpos=barpos	array[n]; type: numeric; default: 0.5*yin
			specifies the position along each bar where string
			barname is plotted. For vertical bars the string is
			plotted with orientation of 90 degrees, along the left
			side of the bar at the height indicated by barpos.
			By default, the string is plotted halfway along the height
			of the bar.
	vertical=vertical
			scalar; type: integer; default: 1
			draw vertical bars (i.e. standard histogram style)
	horizontal=horizontal
			scalar; type: integer: default: 0
			draw horizontal bars

	shade=shade	1- or 2-element array; type: float; default: none
			if set then the bars are shaded.
			    shade[0] is used for bars with good values
			    shade[1] is used for bars with bad values
	hatch=hatch	1- or 2-element array; type: float; default: none
			if set then the bars are hatched. The value determines
			the distance between the hatch lines.
			    hatch[0] is used for bars with good values
			    hatch[1] is used for bars with bad values
	/noline 	If either shade or hatch is set then this suppress
			the bounding line for each bar.
			This keyword is ignored if neither hatch nor shade is set.
	/nojoin 	If barwidth is set to one (the default), then the
			common boundaries between neighbouring bars in not drawn.
			This keyword is ignored if barwidth not equal 1.

	/cdf		Plots a CDF (cumulative distribution function)
			i.e. the yin array is summed left to right.
	/ccdf		Plots the CCDF (complementary cumulative distribution
			function (i.e. the yin array is summed right to left.

	/relative	Plots a normalized CDF. The normalization factor is
			the last element in the CDF.
 INCLUDE
	@compile_opt.pro	    ; On error, return to caller
 CALLS: ***
	BadValue, InitVar, IsType, PlotPrep, REVERSE, destroyvar, gridgen, plotbars_boundary
	plotbars_collect, plotbars_plot, plotbars_shade, plotbars_sigma
 CALLED BY:
	ark_duty_cycle, fileset_sizes, krill_request_stats, packet_size_graphs
	plotcolumns, telescope_sizes
 PROCEDURE:
 MODIFICATION HISTORY:
	OCT-2010, Paul Hick (UCSD/CASS)
	JUL-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Added /use_min_barwidth


plotbars_boundary $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars_boundary.pro
[Previous] [Next]
 NAME:
	plotbars_boundary
 PURPOSE:
	(Internal use by plotbars only)
 CATEGORY:
	ucsd/gen/idl/toolbox/graphics
 CALLING SEQUENCE:
	FUNCTION plotbars_boundary, j, jfirst, jlast, fpnt, negative_side, positive_side, low_margin, $
	    nojoin	 = nojoin	, $
	    bad_sequence = bad_sequence , $
	    cdf 	 = cdf
 INPUTS:
	j
	jfirst
	jlast
	fpnt
	hegative_side
	positive_side
	low_margin
 OPTIONAL INPUT PARAMETERS:
	/nojoin
	/bad_sequence
 OUTPUTS:
	rr[2,n]
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar
 CALLED BY:
	PlotBars
 PROCEDURE:
 MODIFICATION HISTORY:
	MAY-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plotbars_collect $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars_collect.pro
[Previous] [Next]
 NAME:
	plotbars_collect
 PURPOSE:
	(internal use by plotbar only)
 CATEGORY:
	ucsd/gen/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO plotbars_collect, rr_all, rr
 INPUTS:
	rr_all[2,n]
	rr[2,m]
 OUTPUTS:
	rr_all[2,k]
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	boost
 CALLED BY:
	PlotBars
 PROCEDURE:
 MODIFICATION HISTORY:
	MAY-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plotbars_plot $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars_plot.pro
[Previous] [Next]
 NAME:
	plotbars_plot
 PURPOSE:
	(internal use by plotbar only)
 CATEGORY:
	ucsd/gen/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO plotbars_plot, rr, horizontal=horizontal, _extra=_extra
 INPUTS:
	rr[2,n]
 OPTIONAL INPUT PARAMETERS:
	/horizontal
	_extra=_extra
 OUTPUTS:
	(none)
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, IsType, destroyvar
 CALLED BY:
	PlotBars
 PROCEDURE:
 MODIFICATION HISTORY:
	DEC-2010, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plotbars_shade $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars_shade.pro
[Previous] [Next]
 NAME:
	plotbars_shade
 PURPOSE:
	(internal use by plot only)
 CATEGORY:
	ucsd/gen/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO plotbars_shade, rr, $
	    color	= color     , $
	    shading	= shading   , $
	    hatching	= hatching  , $
	    spacing	= spacing   , $
	    horizontal	= horizontal
 INPUTS:
	rr[2,n]
 OPTIONAL INPUT PARAMETERS:
	color=color
	shading=shading
	/hatching
	/spacing
	/horizontal
 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar
 CALLED BY:
	PlotBars
 PROCEDURE:
 MODIFICATION HISTORY:
	MAY-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plotbars_sigma $SMEI/ucsd/gen/idl/toolbox/graphics/plotbars_sigma.pro
[Previous] [Next]
 NAME:
	plotbars_sigma
 PURPOSE:
	(internal use by plot bar only)
 CATEGORY:
	ucsd/gen/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO plotbars_sigma, opnt, fpnt, sigma, horizontal=horizontal
 INPUTS:
	opnt
	fpnt
	sigma
 OPTIONAL INPUT PARAMETERS:
	/horizontal
 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar
 CALLED BY:
	PlotBars
 PROCEDURE:
 MODIFICATION HISTORY:
	MAY-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


plotcolumns $SMEI/ucsd/gen/idl/toolbox/graphics/plotcolumns.pro
[Previous] [Next]
 NAME:
	plotcolumns
 PURPOSE:
	Makes a stack plot.

	Input is provided for n 'groups'. The groups are plotted
	as n separate collections of columns (of one or more columns
	per collection) along the x-axis.

	Example: 10 groups describing the years 2001 through 2010.
	The x-axis will have labels 2001, 2002, ..., 2010 with
	collections of columns near each label.

	Each group (optionally) can contain m 'items'.
	The collection of columns for each group consists of m columns
	(one for each item).
.
	Example: each group has 4 items, one for each quarter of
	the year.

	Each item in the group can have l categories. The l categories
	are stacked on top of each other for each item column.

	Example: categories 'coffee','tea','water','beer','soda'. The input
	data could be ounces of liquid consumed for each category
	per quarter for the years 2001 through 2010.

	For the example:

	xvalues = [2001,2002,...,2010] = array(10)
	yvalues = array(10,4,5) ounces for 10 years, 4 quarter, 5 categories
	item_names = ['Q1','Q2','Q3','Q4']
	stack_names = ['coffee','tea','water','beer','soda']

 CALLING SEQUENCE:
	PRO plotcolumns, xvalues, yvalues, $
	    item_names	    = item_names    , $
	    stack_names     = stack_names   , $
	    stack_empty     = stack_empty   , $
	    group_spacing   = group_spacing , $
	    item_spacing    = item_spacing  , $
	    sort_stack	    = sort_stack    , $
	    label_stack     = label_stack   , $
	    stack_format    = stack_format  , $
	    top_stacks	    = top_stacks    , $
	    stack_colors    = stack_colors  , $
	    legend	    = legend	    , $
	    silent	    = silent	    , $
	    xalign	    = xalign	, $
	    _extra	    = _extra
 INCLUDE:
	@compile_opt.pro
 INPUTS:
	xvalues     array[n]; type: string or numeric
	yvalues     array[n,m,l], array[n,l]; type: numeric
			values for m 'items' in l 'stacks'
			for n 'ngroups'
 OPTIONAL INPUTS:
	item_names=item_names
		    array[m]; type: string; default: none
		    NOT USED YET
		    string labels for the 'm' items
	stack_names=stack_names
		    array[l]; type: string; default: none
		    string labels for the 'l' stacks
		    used in the legend (see below)
	group_spacing=group_spacing
		    scalar; type: integer >= 0; default: 1
		    sets the space between the 'n' groups
		    in units of the column width.
	item_spacing=item_spacing
		    scalar; type: integer >=0; default: group_spacing
		    sets the space between the 'm' items
		    of a group in units of the column width.
	sort_stacks=sort_stacks
		    scalar; type: integer; default: 0
		    allowed values: 0,1,2
		    1: sort the stacks in order of decreasing
		       value of the sums yvalues[*,0,l],
		       i.e. the sum of the values in group 0
		    2: sort the stacks in order of decreasing
		       value of the sums yvalues[*,*,l],
		       i.e. the sum of the values in all groups
		    The first stack in this order will be
		    plotted at the bottom of each column.
	top_stacks=top_stacks
		    scalar; type: integer; default: none
		    if the input array yvalues contains more than
		    'top_stacks' stacks (l > top_stacks), then
		    only 'top_stacks-1' stacks from yvalues are
		    used, and one stack is added containing the
		    sum of the stacks 'top_stacks-1' to 'l-1'.
		    If top_stacks is set then also 'sort_stacks'
		    is assumed set to at least 1.
	stack_colors=stack_colors
		    array[l]; type: integer
		    the color indices to be used to color the
		    'l' stacks in each column
	legend=legend
		    array[2], array[4] or array[6]
		    determines the layout of the legend of 'l'
		    colored blocks for each stack member, with
		    next to it the corresponding 'stack_name' string.
		    All numbers are in normal coordinates
		    legend[0:1]: upper-left corner of legend.
		    legend[2]  : horizontal distance between
				 color block and label
		    legend[3]  : vertical distance between color blocks
		    legend[4]  : length of color block
		    legend[5]  : height of color block
	xalign=xalign
		    scalar; type: numeric between 0 and 1; default: 0
		    By default the label for each group is plotted at the
		    left side of the collection of columns for each group.
		    The location can be controlled with xalign; e.g.
		    xalign=0.5 will center the label on the collection
		    of columns for each group.
	silent=silent
 CALLS: ***
	InitVar, IsType, LOADCT, PlotBars, REVERSE, WhatIs
 CALLED BY:
	krill_request_bars
 PROCEDURE:
	The bargraph produced consists of m x n columns:
	a group of m consecutive columns, repeated n times.
	Each column shows the numbers for the l stacks
	stacked on top of each other.

 MODIFICATION HISTORY:
	DEC-2012, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PlotCoronagraph $SMEI/ucsd/sat/idl/toolbox/graphics/plotcoronagraph.pro
[Previous] [Next]
 NAME:
	PlotCoronagraph
 PURPOSE:
	Plot sky map, with locations of point sources overplotted (optional)
 CATEGORY:
	sat/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO PlotCoronagraph, UT, RA, DEC, F, $
	    equator	= equator	, $
	    maxelo	= maxelo	, $
	    minelo	= minelo	, $
	    drawelo	= drawelo	, $
	    degrees	= degrees	, $
	    mirror	= mirror	, $
	    noerase	= noerase	, $
	    breakval	= breakval	, $
	    basebreak	= basebreak	, $
	    logscale	= logscale	, $
	    charsize	= charsize	, $
	    title	= title 	, $
	    upto	= upto		, $
	    scale	= scale 	, $
	    zero_point	= zero_point	, $
	    zero_phase	= zero_phase	, $
	    dabg	= dabg		, $
	    format	= format	, $
	    fill2edge	= fill2edge	, $
	    _extra	= _extra	, $
	    galactic	= galactic	, $
	    silent	= silent	, $
	    goodcolor	= goodcolor	, $
	    badcolor	= badcolor	, $

	    sn_position = sn_position	, $
	    we_position = we_position	, $
	    ut_position = ut_position	, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $

	    body	= body		, $

	    point_sources=point_sources , $
	    point_names = point_names	, $
	    point_size	= point_size	, $
	    point_onesize=point_onesize , $

	    position	= position	, $
	    legend	= legend	, $
	    compass	= compass	, $
	    max_dec	= max_dec	, $
	    ra_step	= ra_step	, $
	    dec_step	= dec_step	, $
	    naked	= naked
 INPUTS:
	UT	    scalar; type: standard time structure
			time; determines position of Sun in the sky
	RA	    array[n]; type: float
			array of ecliptic longitudes or right ascensions
			(if /equator set) in the range [-180,+180]
			(values are mapped into this range if they are not)
	DEC	    array[m]; type: float
			array of ecliptic latitudes or declinations
			(if /equator is set) in the range [-90,90]
	F	    array[n,m]; type: float
			array of function values in sky map; each function value
			refers to bin on the sky. The edges of the skybin are
			specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
	breakval    array[*]; type: integer or float
			levels between colors (passed to ColorSkybox)
			if not set, a set of break values is calculated
			equally spaced between minimum and maximum
	/logscale   if set, changes to logarithmic scale
	/degrees    if set, indicates that all angles are in degrees
			Default: radians.
	maxelo	    scalar; type: float
			fish-eye map out to elongation 'maxelo'
	minelo	    scalar; type: float
			Erases plot inside of minelo
	drawelo     scalar or array; type: float; default: maxelo
			elongations of circles to be plotted
	/equator    if set, the 'horizontal' in the sky map is parallel
			to the equatorial plane. By default the horizontal
			is along the ecliptic
	upto=upto   scalar; type: integer; default: TimeUnit(/hour)
			controls the length of the UT string plotted
	scale=scale scalar; type: float; default: 1.0
			controls the overall size of the skymap relative
			to the plot window
	/galactic   if set, add a line for the galactic plane

	/naked	    plots the skymap without any labeling or axes.

	goodcolor = goodcolor
		    scalar; type: integer; default: !d.n_colors-1
	badcolor  = badcolor
		    scalar; type: integer; default: !p.color

	/compass
	compass=compass
		    /compass will add label 'E' to left, and 'W' to
			right side of plot. To customize labeling specify
			2-element string (i.e. /compass is the same as
			compass=['E','W'])
	sn_position=sn_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of South/North
			labels. Units are percentages of the window size.
	we_position=we_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of East/West
			labels.
	ut_position=ut_position
		    array[2]; type: real
			x,y coordinates for shifts of UT time label

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

	point_sources=point_sources
		    array; type: sky_point_source structure
			contains information about point sources to be
			overplotted on the skymap.
			See vu_point_source.
	/point_names
		    if set, then the names of the point sources are plotted

	point_size=point_size
		    scalar or array[2]; controls the size of the circles
		    used to plot the point source position. The size is
		    specified in radians or degrees (depending on setting
		    of /degrees).

		    point_size[0]: minimim size of circle.
		    point_size[1]: increment in circle size per unit of
			the function value in skymap F.

		    point_size[1] is used to increase the circle size
		    proportional to the difference between the point
		    source fnc value and the value in the skymap F.

		    If point_size[1] is not set bad (and /point_onesize is
		    NOT set) then only sources with valid function values
		    will be plotted. (I.e. to plot only good sources with
		    the same cirle size set point_size[1] to zero.)

		    If point_size[1] is bad or omitted then /point_onesize
		    is assumed set.

	/point_onesize
		    if set then all sources (including those with bad
		    fnc values) are plotted with the same size circle
		    point_size[0]. This is useful to override the
		    information stored in 'point_sources' or in keyword
		    element point_size[1].

		    If only IPS sources are plotted (i.e. if no skymap
		    F is specified) then setting /point_onesize will plot
		    all source position with the same size.

	The following three keywords are clumsy to use. The idea is to
	control the orientation of the map (i.e. direction of origin,
	and tilt of horizontal on sky). vu_earthskymap uses these
	keywords to set up sky 'snapshots'.

	dabg	    array[3]; type: float; default: [0,0,0]
			(used by the projection functions FishEye,
			HammerAitoff and MercatorProj, either directly in
			this procedure or indirectly in ColorSkybox)

	zero_point  scalar; type: float; default: centered on Sun
			(used internally and passed to FishEye,
			HammerAitoff and MercatorProj). Defines the
			longitude or RA of the center of the FishEye,
			HammerAitoff or Mercator map.

	zero_phase  scalar, or array with same structure as 'RA';
		    type: float; default: zero_point
			(passed to ColorSkybox)
			ColorSkybox uses this keyword to rearrange its
			first three arguments (RA,DEC and fnc-values) to
			put zero_phase in the center of the map. This
			modifies input arrays RA and DEC, but not F.
			zero_phase is not used if F does not exist on
			input, i.e. if only point sources are plotted
			(in this case the RA and DEC arrays don't exist
			either).

	For sky 'snapshots' zero_phase is the same as zero_point.

	Keywords passed to ColorSkybox:

	use_mask = use_mask
	mask=mask
 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
	@vu_fnc_include.pro	;
 CALLS: ***
	AngleRange, BadValue, ColorSkybox, CvSky, EulerRotate, FishEye, GetColors [1]
	GetColors [2], GetColors [3], INTERPOL, InitVar, IsType, MEAN, PlotUserstring
	SuperArray, TimeGet, TimeUnit, ToDegrees, ToRadians, anicenum, big_eph, gridgen
	sphere_distance, vu_fnc, vu_point_source
 CALLED BY:
	vu_coronagraph
 PROCEDURE:
	Based on PlotEarthSkymap
 MODIFICATION HISTORY:
	MAR-2011, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PlotCurve $SMEI/ucsd/gen/idl/toolbox/graphics/plotcurve.pro
[Previous] [Next]
 NAME:
	PlotCurve
 PURPOSE:
	(Over)plot two arrays x, y. Connect only `valid' points.
 CALLING SEQUENCE:
	PRO PlotCurve, xin, y, nvalid, $
	    sigma	= sigma      , $
	    oplotx	= oplotx     , $
	    xrange	= xrange     , $
	    newyaxis	= newyaxis   , $
	    yaxis	= yaxis      , $
	    ynozero	= ynozero    , $
	    ylog	= ylog	     , $
	    yrange	= yrange     , $
	    ystyle	= ystyle     , $
	    color	= color      , $
	    changecolor = changecolor, $
	    _extra	= _extra     , $
	    silent	= silent     , $
	    bar 	= bar	     , $
	    shade	= shade      , $
	    hatch	= hatch      , $
	    noline	= noline
 INPUTS:
	x,y		one-dimensional arrays; must have the same size
	nvalid		identifies the array elements to be plotted as:
			- an array of indices e.g. [0,1,2,7,8,9,10]
			- a boolean array (containing only values 0 or 1)
			of same size as x and y, e.g. [1,1,1,0,0,0,0,1,1,1,1]
			if nvalid is absent, all finite function values are plotted
 OPTIONAL INPUT PARAMETERS:
	/oplot		if not set, then a new plot (with a new x-axis) is started)
			    (implicitly /newaxis is set and yaxis=-1, i.e. a y-axis
			    will be drawn on the left)
			if set, then the arrays are overplotted on a previous plot
			    (the keywords /newyaxis and yaxis=yaxis can be used to add
			    additional y axes, if necessary)
	/newyaxis
			adds a new yaxis (if /oplot is NOT set, then /newaxis is assumed set)
	yaxis=yaxis	controls the position of a new y axis; yaxis is used only if /newaxis is set
			yaxis=-1 : y-axis on left (default)
			yaxis=0  : y-axis on right
			0<yaxis<1: y-axis is placed in the right margin
			    (if this is used then ymargin must be made big enough
			    to hold the extra y axis).
	sigma=sigma	array; type: any
			    must have same size as x,y. Standard deviations of y-data
	color=color	scalar or array[2]; type: integer; default: [!p.color, !d.n_color-1]
			    color indices used to connect points.
			    color[0] is used to connect good data points
			    color[1] is used to connect bad data points (if /change is set)
	/change 	by default, bad data points are not plotted. If /change is set
			bad points are connected with color[1]

	/bar		if set then a bar graph is drawn
	shade=shade	scalar or array[2]; type: any; default: none
			    if /bar is set then shade[0] is used to shade good data bars
			    and (if /change) is set shade[1] is used to shade bad bars
	hatch=hatch	scalar or array[1]; type: any: default: none
			    if /bar is set then hatch[0] is used to shade good data bars
			    and (if /change) is set shade[1] is used to shade bad bars
	/noline 	(only used if /bar is set)
			Suppress line drawing (i.e. only shade or hatch)

	IDL plot keywords:
	    xmargin, ymargin	    used only to start a new plot (/oplot NOT set)
	    yrange, ynozero	    used only if new y-axis is plotted
				    (/oplot NOT set, or /newaxis set)
				    ynozero is NOT used if yrange is specified
	    linestyle, xtitle, ytitle, psym, charsize
 INCLUDE
	@compile_opt.pro	    ; On error, return to caller
 CALLED BY:
	GetColors [2], GetColors [3], InSitu, PlotEarthSkymap [1], PlotEarthSkymap [2]
	PlotEarthSkymap [3], PlotEarthSkymap [4], PlotEloTimeMap, PlotPolarSkymap
	eclipsed_area, edit_smei, editsmei, even_light_registration, jpl_test, laserjet
	losgeometry, miscfig, qLine_Curve, qnew_2007_013, smei_frm_darkfit
	smei_frm_summary, smei_hdr_plot, smei_normal, smei_plot_timeseries
	smei_star_show, thomsonfig, ulysses_passage, vu_insitucurve, vu_linecut, vu_losmap
	vu_radialcut, vu_thomson_antifish, vu_thomson_hammer
 COMMON BLOCKS:
	common TimeScale, torigin, trange, tunit, texact	; Set by TimeXAxis
 CALLS: ***
	InitVar, IsTime, IsType, TimeOp, TimeSet, TimeXAxis
 RESTRICTIONS:
	There still seems to be a problem with the axis plotting: once a log axis has been
	plotted all added curves will also have a logarithmic scale, i.e. ylog=0 setting does not
	have any effect. This appears to be a bug in the IDL axis routine.
 PROCEDURE:
>	Only valid data points are connected by the type of line specified
	by the linestyle keyword.
>	Valid data points are identified in the nvalid array either by their
	array index or by a boolean value of 1.
 MODIFICATION HISTORY:
	APR-1996, Paul Hick (UCSD/CASS)
	OCT-1999, Paul Hick (UCSD/CASS)
	    if nvalid is not specified only finite y-values (finite(y) = 1) are
	    plotted, instead of all points
	FEB-2001, Paul Hick (UCSD/CASS)
	    Fixed minor bug in handling of invalid data points.
	FEB-2004, Paul Hick (UCSD/CASS)
	    Fixed bug for call with a time array as x-array when the time
	    origin is not yet defined
	SEP-2007, Paul Hick (UCSD/CASS)
	    Added keywords bar, hatch and shade for plotting bar graphs
	JUL-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Added xrange keyword to allo


PlotCurves $SMEI/ucsd/gen/idl/toolbox/graphics/plotcurves.pro
[Previous] [Next]
 NAME:
	PlotCurves
 PURPOSE:
	(Over)plot two arrays x, y. Connect only `valid' points.
 CALLING SEQUENCE:
	PRO PlotCurves, xin, yin, nvalid, $
	    sigma	= sigma 	, $
	    xrange	= xrange	, $
	    yaxis	= yaxis 	, $
	    ynozero	= ynozero	, $
	    ylog	= ylog		, $
	    yrange	= yrange	, $
	    ystyle	= ystyle	, $
	    ycolor	= ycolor	, $
	    color	= color 	, $
	    changecolor = changecolor	, $
	    nodata	= nodata	, $
	    markoutside = markoutside	, $
	    _extra	= _extra
 INPUTS:
	Input arguments passed to PlotPrep:

	xin, yin	abcissa and ordinate arrays;
	nvalid		identifies the array elements to be plotted
 OPTIONAL INPUT PARAMETERS:
	Keywords passed to PlotPrep:

	/oplotx 	if set, then overplot on plot set up by
			previous call to PlotCurves
	/newyaxis	adds a new yaxis (if /oplot is NOT set, then /newaxis is assumed set)
	yaxis=yaxis	controls the position of a new y axis

	/changecolor	by default, bad data points are not plotted.
			If /changecolor is set bad points are connected with color[1]
	/nodata 	if set, only the x- and y-axes are drawn. Data points are ignored.
			(effectively this is just a call to PlotPrep).

	Additional keywords:

	sigma=sigma	array; type: any
			    must have same size as x,y.
			    Standard deviations of y-data
	color=color	scalar or array[2]; type: integer; default: [!p.color, !d.n_color-1]
			    color indices used to connect points.
			    color[0] is used to connect good data points
			    color[1] is used to connect bad data points (if /changecolor is set)
	ycolor=ycolor	scalar; type: integer; default: none
			    passed to PlotPrep. Determines the color used to draw the y-axis.
			    Useful to emphasize the association between y-axis and data points
			    if multiple y-axes are used.
	markoutside=markoutside
			scalar, type: integer; default: 0
			    Can be used to make points outside the plot area visible
			    by plotting an arrowhead pressed against the upper or lower
			    x-axis. The value of markoutside determines the size of
			    the arrowhead in device units. A negative value will turn
			    the arrowhead into a solid triangle. The color is
			    taken from the 'color' keyword.
	IDL plot keywords:

	xmargin, ymargin    used only to start a new plot (/oplot NOT set)
	yrange, ynozero     used only if new y-axis is plotted
			    (/oplot NOT set, or /newaxis set)
			    ynozero is NOT used if yrange is specified
	linestyle, xtitle, ytitle, psym, charsize
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, IsType, PlotPrep
 CALLED BY:
	ark_duty_cycle, ipv6_packets, krill_request_stats, packet_size_graphs
	plot_ipv6_fraction, plot_traffic, smei_hdr_plot
 RESTRICTIONS:
	There still seems to be a problem with the axis plotting:
	once a log axis has been plotted all added curves will also
	have a logarithmic scale, i.e. ylog=0 setting does not
	have any effect. This appears to be a bug in the IDL axis routine.
 PROCEDURE:
>	Only valid data points are connected by the type of line specified
	by the linestyle keyword.
>	Valid data points are identified in the nvalid array either by their
	array index or by a boolean value of 1.
 MODIFICATION HISTORY:
	APR-1996, Paul Hick (UCSD/CASS)
	OCT-1999, Paul Hick (UCSD/CASS)
	    if nvalid is not specified only finite y-values (finite(y) = 1) are
	    plotted, instead of all points
	FEB-2001, Paul Hick (UCSD/CASS)
	    Fixed minor bug in handling of invalid data points.
	FEB-2004, Paul Hick (UCSD/CASS)
	    Fixed bug for call with a time array as x-array when the time
	    origin is not yet defined
	SEP-2007, Paul Hick (UCSD/CASS)
	    Added keywords bar, hatch and shade for plotting bar graphs
	JUL-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Added xrange keyword


PlotDashes $SMEI/ucsd/gen/idl/toolbox/graphics/plotdashes.pro
[Previous] [Next]
 NAME:
	PlotDashes
 CALLING SEQUENCE:
	PRO PlotDashes, x, y, $
	    dashes	= dashes    , $
	    absolute	= absolute  , $
	    _extra	= _extra
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	InitVar, destroyvar


PlotEarthSkymap [1] $SMEI/ucsd/sat/idl/toolbox/graphics/plotearthskymap.pro
[Previous] [Next]
 NAME:
	PlotEarthSkymap
 PURPOSE:
	Plot sky map, with locations of point sources overplotted (optional)
 CATEGORY:
	sat/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO PlotEarthSkymap, UT, RA, DEC, F, $
	    equator	    = equator	    , $
	    maxelo	    = maxelo	    , $
	    minelo	    = minelo	    , $
	    geolng	    = geolng	    , $
	    degrees	    = degrees	    , $
	    mirror	    = mirror	    , $
	    noerase	    = noerase	    , $
	    breakval	    = breakval	    , $
	    basebreak	    = basebreak     , $
	    logscale	    = logscale	    , $
	    charsize	    = charsize	    , $
	    title	    = title	    , $
	    upto	    = upto	    , $
	    scale	    = scale	    , $
	    zero_point	    = zero_point    , $
	    zero_phase	    = zero_phase    , $
	    dabg	    = dabg	    , $
	    format	    = format	    , $
	    fill2edge	    = fill2edge     , $
	    _extra	    = _extra	    , $
	    galactic	    = galactic	    , $
	    silent	    = silent	    , $
	    goodcolor	    = goodcolor     , $
	    badcolor	    = badcolor	    , $

	    sn_position     = sn_position   , $
	    we_position     = we_position   , $
	    ut_position     = ut_position   , $
	    user_position   = user_position , $
	    user_align	    = user_align    , $
	    user_string     = user_string   , $

	    body	    = body	    , $

	    point_sources   = point_sources , $
	    point_names     = point_names   , $
	    point_size	    = point_size    , $
	    point_onesize   = point_onesize , $

	    position	    = position	    , $
	    legend	    = legend	    , $
	    compass	    = compass	    , $
	    max_dec	    = max_dec	    , $
	    ra_step	    = ra_step	    , $
	    dec_step	    = dec_step	    , $
	    naked	    = naked
 INPUTS:
	UT	    scalar; type: standard time structure
			time; determines position of Sun in the sky
	RA	    array[n]; type: float
			array of ecliptic longitudes or right ascensions
			(if /equator set) in the range [-180,+180]
			(values are mapped into this range if they are not)
	DEC	    array[m]; type: float
			array of ecliptic latitudes or declinations
			(if /equator is set) in the range [-90,90]
	F	    array[n,m]; type: float
			array of function values in sky map; each function value
			refers to bin on the sky. The edges of the skybin are
			specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
	breakval    array[*]; type: integer or float
			levels between colors (passed to ColorSkybox)
			if not set, a set of break values is calculated
			equally spaced between minimum and maximum
	/logscale   if set, changes to logarithmic scale
	/degrees    if set, indicates that all angles are in degrees
			Default: radians.
	maxelo	    scalar; type: float
			used to decide on map projection
			> 0: fish-eye map out to elongation 'maxelo'
			= 0: Mercator projection (similar to synoptic map)
			< 0: Hammer-Aitoff projection
			if absent then a Hammer-Aitoff map is drawn
	minelo	    scalar; type: float
			Erases plot inside of minelo
	/equator    if set, the 'horizontal' in the sky map is parallel
			to the equatorial plane. By default the horizontal
			is along the ecliptic
	upto=upto   scalar; type: integer; default: TimeUnit(/hour)
			controls the length of the UT string plotted
	scale=scale scalar; type: float; default: 1.0
			controls the overall size of the skymap relative
			to the plot window
	/galactic   if set, add a line for the galactic plane

	/naked	    plots the skymap without any labeling or axes.

	goodcolor = goodcolor
		    scalar; type: integer; default: !d.n_colors-1
	badcolor  = badcolor
		    scalar; type: integer; default: !p.color

	/compass
	compass=compass
		    /compass will add label 'E' to left, and 'W' to
			right side of plot. To customize labeling specify
			2-element string (i.e. /compass is the same as
			compass=['E','W'])
	sn_position=sn_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of South/North
			labels. Units are percentages of the window size.
	we_position=we_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of East/West
			labels.
	ut_position=ut_position
		    array[2]; type: real
			x,y coordinates for shifts of UT time label

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

	point_sources=point_sources
		    array; type: sky_point_source structure
			contains information about point sources to be
			overplotted on the skymap.
			See vu_point_source.
	/point_names
		    if set, then the names of the point sources are plotted

	point_size=point_size
		    scalar or array[2]; controls the size of the circles
		    used to plot the point source position. The size is
		    specified in radians or degrees (depending on setting
		    of /degrees).

		    point_size[0]: minimim size of circle.
		    point_size[1]: increment in circle size per unit of
			the function value in skymap F.

		    point_size[1] is used to increase the circle size
		    proportional to the difference between the point
		    source fnc value and the value in the skymap F.

		    If point_size[1] is not set bad (and /point_onesize is
		    NOT set) then only sources with valid function values
		    will be plotted. (I.e. to plot only good sources with
		    the same cirle size set point_size[1] to zero.)

		    If point_size[1] is bad or omitted then /point_onesize
		    is assumed set.

	/point_onesize
		    if set then all sources (including those with bad
		    fnc values) are plotted with the same size circle
		    point_size[0]. This is useful to override the
		    information stored in 'point_sources' or in keyword
		    element point_size[1].

		    If only IPS sources are plotted (i.e. if no skymap
		    F is specified) then setting /point_onesize will plot
		    all source position with the same size.

	The following three keywords are clumsy to use. The idea is to
	control the orientation of the map (i.e. direction of origin,
	and tilt of horizontal on sky). vu_earthskymap uses these
	keywords to set up sky 'snapshots' and sky 'sweeps'.

	dabg	    array[3]; type: float; default: [0,0,0]
			(used by the projection functions FishEye,
			HammerAitoff and MercatorProj, either directly in
			this procedure or indirectly in ColorSkybox)

	zero_point  scalar; type: float; default: centered on Sun
			(used internally and passed to FishEye,
			HammerAitoff and MercatorProj). Defines the
			longitude or RA of the center of the FishEye,
			HammerAitoff or Mercator map.

	zero_phase  scalar, or array with same structure as 'RA';
		    type: float; default: zero_point
			(passed to ColorSkybox)
			ColorSkybox uses this keyword to rearrange its
			first three arguments (RA,DEC and fnc-values) to
			put zero_phase in the center of the map. This
			modifies input arrays RA and DEC, but not F.
			zero_phase is not used if F does not exist on
			input, i.e. if only point sources are plotted
			(in this case the RA and DEC arrays don't exist
			either).

	For sky 'snapshots' zero_phase is the same as zero_point.
	For sky 'sweeps' zero_phase is a monotonic array with a value
	for each sweep, and the value of 'zero_point' (almost) exactly
	in the center of 'zero_phase'. Note that inconsistent settings
	of zero_point and zero_phase make an incorrect map.

	Keywords passed to ColorSkybox:

	use_mask = use_mask
	mask=mask
 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
	@vu_fnc_include.pro	;
 CALLS: ***
	AngleRange, BadValue, ColorSkybox, CvSky, EulerRotate, FishEye, GeographicInfo
	GetColors [1], GetColors [2], GetColors [3], HammerAitoff, INTERPOL, InitVar, IsType
	MEAN, MercatorProj, PlotCurve, PlotUserstring, SuperArray, TimeGet, TimeUnit
	ToDegrees, ToRadians, anicenum, big_eph, gridgen, say, sphere_distance, vu_fnc
	vu_point_source
 CALLED BY:
	GetColors [2], GetColors [3], allsky [1], allsky [2], allsky [3], allsky_f, smei_sky
	smei_zldsky, vu_earthskymap, vu_thomson_antifish, vu_thomson_hammer
 PROCEDURE:
 >	Time UT is needed to calculate the location of equator and ecliptic
 >	The ecliptic is drawn on an equatorial skymap and v.v
 >	Longitude/RA is plotted increasing right-to-left across the map
	(as it is for a viewer at Earth looking up at the sky). For
	sun-centered maps this means that east is left and west is right.
	A mirror image of the map can be made by setting keyword /mirror.
 > The data range for the horizontal axis is -180,+180 degrees
	relative to 'zero_point' as needed for the Hammer-Aitoff and
	fisheye projections. I.e. longitude/RA 'zero_point' will
	appear at the center of the map.
 > For the fisheye maps the center is at location (longitude,latitude
	or RA/dec) zero_point+dabg[0],-dabg[1]

 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS)
	FEB-2002, Paul Hick (UCSD/CASS)
	    Added option to plot a sky map in Mercator projection
	    by setting maxelo=0.
	APR-2002, Paul Hick (UCSD/CASS)
	    Added /fill2edge keyword (passed to ColorSkybox)
	SEP-2003, Paul Hick (UCSD/CASS)
	    Minor tweaking of labels to get Mercator projection to
	    look better. Added /galactic keyword.
	AUG-2004, Paul Hick (UCSD/CASS)
	    Started adding some code to deal with Thomson scattering
	    brightness (mainly for overplotting point sources).
	    The time plotted at the top is now rounded instead of
	    truncating to timeunit 'upto'.
	SEP-2004, Paul Hick (UCSD/CASS)
	    For fisheye plots point sources with outside maxelo are
	    not plotted anymore.
	    Reworked the determination of the circle sizes for the
	    point sources, and added some keywords to control them.
	SEP-2006, Paul Hick (UCSD/CASS)
	    Modified default for zero_point. Was zero, now is ecliptic
	    longitude/RA of Sun. This automatically centers the Sun
	    if only point sources are plotted
	    (as by vu_nagoyasourcemap).
	JUL-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Modified way the Sun is marked for fish-eye plots.
	    If outside the plot for fishe-eye maps then the Sun is
	    not marked at all, or (if dabg exists) the direction to
	    the Sun is marked with a tickmark on the outer edge.


PlotEarthSkymap [2] $SMEI/user/jclover/from_ztemp/allsky_af.pro
[Previous] [Next]
 NAME:
   PlotEarthSkymap
 PURPOSE:
   Plot sky map, with locations of point sources overplotted (optional)
 CATEGORY:
   www
 CALLING SEQUENCE:
   PlotEarthSkyMap, UT, RA, DE, F
 INPUTS:
   UT	      scalar; type: standard time structure
	     time; determines position of Sun in the sky
   RA	      array[n]; type: float
	     array of ecliptic longitudes or right ascensions
	     (if /equator set) in the range [-180,+180]
	     (values are mapped into this range if they are not)
   DEC	    array[m]; type: float
	     array of ecliptic latitudes or declinations
	     (if /equator is set) in the range [-90,90]
   F	    array[n,m]; type: float
	     array of function values in sky map; each function value
	     refers to bin on the sky. The edges of the skybin are
	     specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
   breakval  array[*]; type: integer or float
	     levels between colors (passed to ColorSkybox)
	     if not set, a set of break values is calculated
	     equally spaced between minimum and maximum
   /log   if set, changes to logarithmic scale
   /degrees  if set, indicates that all angles are in degrees
	     Default: radians.
   maxelo	scalar; type: float
	     used to decide on map projection
	     > 0: fish-eye map out to elongation 'maxelo'
	     = 0: Mercator projection (similar to synoptic map)
	     < 0: Hammer-Aitoff projection
	     if absent then a Hammer-Aitoff map is drawn
   minelo	scalar; type: float
	     Erases plot inside of minelo
   /equator  if set, the 'horizontal' in the sky map is parallel to the
	     equatorial plane. By default the horizontal is along the ecliptic
   upto=upto scalar; type: integer; default: TimeUnit(/hour)
	     controls the length of the UT string plotted
   scale=scale	 scalar; type: float; default: 1.0
	     controls the overall size of the skymap relative to the plot window
   /galactic if set, add a line for the galactic plane

   goodcolor = goodcolor
	  scalar; type: integer; default: !d.n_colors-1
   badcolor  = badcolor
	  scalar; type: integer; default: !p.color

   sn_position=sn_position
	  array[4]; type: real
	     Pairs of x,y coordinates for shifts of South/North labels
	     Units are percentages of the window size
   we_position=we_position
	  array[4]; type: real
	     Pairs of x,y coordinates for shifts of East/West labels
   ut_position=ut_position
	  array[2]; type: real
	     x,y coordinates for shifts of UT time label

   user_string=user_string
	  scalar; type: string
	     User specified string to be plotted
   user_position=user_position
	  array[2]; type: real
	     Position of user string in normal coordinates

   point_sources=point_sources
	  array; type: sky_point_source structure
	     contains information about point sources to be overplotted
	     on the skymap. See vu_point_source.
   /point_names
	  if set, then the names of the point sources are plotted

   point_size=point_size
	  scalar or array[2]; controls the size of the circles used to plot the
	  point source position. The size is specified in radians or degrees
	  (depending on setting of /degrees).

	  point_size[0]: minimim size of circle.
	  point_size[1]: increment in circle size per unit of the function
	     value in skymap F.

	  point_size[1] is used to increase the circle size proportional to
	  the difference between the point source fnc value and the value in
	  the skymap F.

	  If point_size[1] is not set bad (and /point_onesize is NOT set)
	  then only sources with valid function values will be plotted.
	  (I.e. to plot only good sources with the same cirle size set
	  point_size[1] to zero.)

	  If point_size[1] is bad or omitted then /point_onesize is assumed set.

   /point_onesize
	  if set then all sources (including those with bad fnc values)
	  are plotted with the same size circle point_size[0].
	  This is useful to override the information stored
	  in 'point_sources' or in keyword element point_size[1].

	  If only IPS sources are plotted (i.e. if no skymap F is specified) then
	  setting /point_onesize will plot all source position with the same size.

   The following three keywords are clumsy to use. The idea is to control the orientation
   of the map (i.e. direction of origin, and tilt of horizontal on sky).
   vu_EarthSkymap uses these keywords to set up sky 'snapshots' and sky 'sweeps'.

   dabg   array[3]; type: float; default: [0,0,0]
	     (used by the projection functions FishEye, HammerAitoff and
	     MercatorProj, either directly in this procedure or indirectly in
	     ColorSkybox)

   zero_point	 scalar; type: float; default: 0.0
	     (used internally and passed to FishEye, HammerAitoff and MercatorProj)
	     Defines the longitude or RA of the center of the FishEye,HammerAitoff
	     or Mercator map.

   zero_phase	 scalar, or array with same structure as 'RA'; type: float; default: zero_point
	     (passed to ColorSkybox)
	     ColorSkybox uses this keyword to rearrange its first three arguments
	     (RA,DEC and fnc-values) to put zero_phase in the center of the map.
	     This modifies input arrays RA and DEC, but not F.

   For sky 'snapshots' zero_phase is the same as zero_point.
   For sky 'sweeps' zero_phase is a monotonic array with a value for each sweep, and
   the value of 'zero_point' (almost) exactly in the center of 'zero_phase'. Note that
   inconsistent settings of zero_point and zero_phase make an incorrect map.
 OUTPUTS:
 INCLUDE:
    @compile_opt.pro	  ; On error, return to caller
 CALLS: ***
	ALLSKY_AF, ARROW, AngleRange, AngleUnits, BadValue, ColorSkybox, CvPrecess, CvSky
	ELONGATION, EulerRotate, FILEPATH, FishEye, GeographicInfo, GetColors [1]
	GetColors [2], GetColors [3], GetFileSpec, HammerAitoff, INTERPOL, InitVar, IsType
	MEAN, MercatorProj, NewcombSun, PlotCurve, STRETCH, SetFileSpec, SuperArray, TimeSet
	TimeString, TimeUnit, ToDegrees, ToRadians, anicenum, array_smooth, bin_read, boost
	destroyvar, flt_string, get_page, gridgen, jpl_body, jpl_close, jpl_eph, reset_colors
	set_page, smei_coriolis, vu_point_source
 CALLED BY:
	GetColors [2], GetColors [3], allsky [1], allsky [2], allsky [3], allsky_f, smei_sky
	smei_zldsky, vu_earthskymap, vu_thomson_antifish, vu_thomson_hammer
 PROCEDURE:
 > Time UT is needed to calculate the location of equator and ecliptic
 > The ecliptic is drawn on an equatorial skymap and v.v
 > Longitude/RA is plotted increasing right-to-left across the map
   (as it is for a viewer at Earth looking up at the sky). For sun-centered maps
   this means that east is left and west is right. A mirror image of the map
   can be made by setting keyword /mirror.
 > The data range for the horizontal axis is -180,+180 degrees relative to
   'zero_point' as needed for the Hammer-Aitoff and fisheye projections. I.e.
   longitude/RA 'zero_point' will appear at the center of the map.
 MODIFICATION HISTORY:
   SEP-1999, Paul Hick (UCSD/CASS)
   FEB-2002, Paul Hick (UCSD/CASS)
     Added option to plot a sky map in Mercator projection by setting maxelo=0.
   APR-2002, Paul Hick (UCSD/CASS)
     Added /fill2edge keyword (passed to ColorSkybox)
   SEP-2003, Paul Hick (UCSD/CASS)
     Minor tweaking of labels to get Mercator projection to look better
     Added /galactic keyword.
   AUG-2004, Paul Hick (UCSD/CASS)
     Started adding some code to deal with Thomson scattering brightness
     (mainly for overplotting point sources).
     The time plotted at the top is now rounded instead of truncating
     to timeunit 'upto'.
   SEP-2004, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
     For fisheye plots point sources with outside maxelo are not plotted anymore
     Reworked the determination of the circle sizes for the point sources, and
     added some keywords to control them.


PlotEarthSkymap [3] $SMEI/user/jclover/from_ztemp/vu_thomson_antifish.pro
[Previous] [Next]
 NAME:
   PlotEarthSkymap
 PURPOSE:
   Plot sky map, with locations of point sources overplotted (optional)
 CATEGORY:
   www
 CALLING SEQUENCE:
   PlotEarthSkyMap, UT, RA, DE, F
 INPUTS:
   UT	      scalar; type: standard time structure
	     time; determines position of Sun in the sky
   RA	      array[n]; type: float
	     array of ecliptic longitudes or right ascensions
	     (if /equator set) in the range [-180,+180]
	     (values are mapped into this range if they are not)
   DEC	    array[m]; type: float
	     array of ecliptic latitudes or declinations
	     (if /equator is set) in the range [-90,90]
   F	    array[n,m]; type: float
	     array of function values in sky map; each function value
	     refers to bin on the sky. The edges of the skybin are
	     specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
   breakval  array[*]; type: integer or float
	     levels between colors (passed to ColorSkybox)
	     if not set, a set of break values is calculated
	     equally spaced between minimum and maximum
   /log   if set, changes to logarithmic scale
   /degrees  if set, indicates that all angles are in degrees
	     Default: radians.
   maxelo	scalar; type: float
	     used to decide on map projection
	     > 0: fish-eye map out to elongation 'maxelo'
	     = 0: Mercator projection (similar to synoptic map)
	     < 0: Hammer-Aitoff projection
	     if absent then a Hammer-Aitoff map is drawn
   minelo	scalar; type: float
	     Erases plot inside of minelo
   /equator  if set, the 'horizontal' in the sky map is parallel to the
	     equatorial plane. By default the horizontal is along the ecliptic
   upto=upto scalar; type: integer; default: TimeUnit(/hour)
	     controls the length of the UT string plotted
   scale=scale	 scalar; type: float; default: 1.0
	     controls the overall size of the skymap relative to the plot window
   /galactic if set, add a line for the galactic plane

   point_sources=point_sources
	  array; type: sky_point_source structure
	     contains information about point sources to be overplotted
	     on the skymap. See vu_point_source.
   /point_names
	  if set, then the names of the point sources are plotted

   point_size=point_size
	  scalar or array[2]; controls the size of the circles used to plot the
	  point source position. The size is specified in radians or degrees
	  (depending on setting of /degrees).

	  point_size[0]: minimim size of circle.
	  point_size[1]: increment in circle size per unit of the function
	     value in skymap F.

	  point_size[1] is used to increase the circle size proportional to
	  the difference between the point source fnc value and the value in
	  the skymap F.

	  If point_size[1] is not set bad (and /point_onesize is NOT set)
	  then only sources with valid function values will be plotted.
	  (I.e. to plot only good sources with the same cirle size set
	  point_size[1] to zero.)

	  If point_size[1] is bad or omitted then /point_onesize is assumed set.

   /point_onesize
	  if set then all sources (including those with bad fnc values)
	  are plotted with the same size circle point_size[0].
	  This is useful to override the information stored
	  in 'point_sources' or in keyword element point_size[1].

	  If only IPS sources are plotted (i.e. if no skymap F is specified) then
	  setting /point_onesize will plot all source position with the same size.

   The following three keywords are clumsy to use. The idea is to control the orientation
   of the map (i.e. direction of origin, and tilt of horizontal on sky).
   vu_EarthSkymap uses these keywords to set up sky 'snapshots' and sky 'sweeps'.

   dabg   array[3]; type: float; default: [0,0,0]
	     (used by the projection functions FishEye, HammerAitoff and
	     MercatorProj, either directly in this procedure or indirectly in
	     ColorSkybox)

   zero_point	 scalar; type: float; default: 0.0
	     (used internally and passed to FishEye, HammerAitoff and MercatorProj)
	     Defines the longitude or RA of the center of the FishEye,HammerAitoff
	     or Mercator map.

   zero_phase	 scalar, or array with same structure as 'RA'; type: float; default: zero_point
	     (passed to ColorSkybox)
	     ColorSkybox uses this keyword to rearrange its first three arguments
	     (RA,DEC and fnc-values) to put zero_phase in the center of the map.
	     This modifies input arrays RA and DEC, but not F.

   For sky 'snapshots' zero_phase is the same as zero_point.
   For sky 'sweeps' zero_phase is a monotonic array with a value for each sweep, and
   the value of 'zero_point' (almost) exactly in the center of 'zero_phase'. Note that
   inconsistent settings of zero_point and zero_phase make an incorrect map.
 OUTPUTS:
 INCLUDE:
    @compile_opt.pro	  ; On error, return to caller
 CALLS: ***
	ARG_TIME, AngleRange, BadValue, ColorSkybox, CvSky, EarthSky3DLoc, EarthTransit3DLoc
	EulerRotate, FILEPATH, FishEye, GeographicInfo, GetColors [1], GetColors [2]
	GetColors [3], GetFileSpec, HammerAitoff, INTERPOL, IPS_params, InitVar
	IntegrateLOS, IsType, LOADCT, MercatorProj, NewcombSun, PlotCurve, REVERSE, STRETCH
	ThomsonRadialFilter, TimeGet, TimeSet, TimeString, TimeUnit, ToDegrees, ToRadians
	UBVCONST, UNIQ, VU_TYPE_SKY, WhatIs, anicenum, destroyvar, flt_read, gridgen
	reset_colors, set_page, vu_earthskymap, vu_get, vu_get_page, vu_getdata, vu_gettime
	vu_point_source, vu_thomson_antifish
 CALLED BY:
	GetColors [2], GetColors [3], allsky [1], allsky [2], allsky [3], allsky_f, smei_sky
	smei_zldsky, vu_earthskymap, vu_thomson_antifish, vu_thomson_hammer
 PROCEDURE:
 > Time UT is needed to calculate the location of equator and ecliptic
 > The ecliptic is drawn on an equatorial skymap and v.v
 > Longitude/RA is plotted increasing right-to-left across the map
   (as it is for a viewer at Earth looking up at the sky). For sun-centered maps
   this means that east is left and west is right. A mirror image of the map
   can be made by setting keyword /mirror.
 > The data range for the horizontal axis is -180,+180 degrees relative to
   'zero_point' as needed for the Hammer-Aitoff and fisheye projections. I.e.
   longitude/RA 'zero_point' will appear at the center of the map.
 MODIFICATION HISTORY:
   SEP-1999, Paul Hick (UCSD/CASS)
   FEB-2002, Paul Hick (UCSD/CASS)
     Added option to plot a sky map in Mercator projection by setting maxelo=0.
   APR-2002, Paul Hick (UCSD/CASS)
     Added /fill2edge keyword (passed to ColorSkybox)
   SEP-2003, Paul Hick (UCSD/CASS)
     Minor tweaking of labels to get Mercator projection to look better
     Added /galactic keyword.
   AUG-2004, Paul Hick (UCSD/CASS)
     Started adding some code to deal with Thomson scattering brightness
     (mainly for overplotting point sources).
     The time plotted at the top is now rounded instead of truncating
     to timeunit 'upto'.
   SEP-2004, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
     For fisheye plots point sources with outside maxelo are not plotted anymore
     Reworked the determination of the circle sizes for the point sources, and
     added some keywords to control them.


PlotEarthSkymap [4] $SMEI/user/jclover/from_ztemp/vu_thomson_hammer.pro
[Previous] [Next]
 NAME:
   PlotEarthSkymap
 PURPOSE:
   Plot sky map, with locations of point sources overplotted (optional)
 CATEGORY:
   www
 CALLING SEQUENCE:
   PlotEarthSkyMap, UT, RA, DE, F
 INPUTS:
   UT	      scalar; type: standard time structure
	     time; determines position of Sun in the sky
   RA	      array[n]; type: float
	     array of ecliptic longitudes or right ascensions
	     (if /equator set) in the range [-180,+180]
	     (values are mapped into this range if they are not)
   DEC	    array[m]; type: float
	     array of ecliptic latitudes or declinations
	     (if /equator is set) in the range [-90,90]
   F	    array[n,m]; type: float
	     array of function values in sky map; each function value
	     refers to bin on the sky. The edges of the skybin are
	     specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
   breakval  array[*]; type: integer or float
	     levels between colors (passed to ColorSkybox)
	     if not set, a set of break values is calculated
	     equally spaced between minimum and maximum
   /log   if set, changes to logarithmic scale
   /degrees  if set, indicates that all angles are in degrees
	     Default: radians.
   maxelo	scalar; type: float
	     used to decide on map projection
	     > 0: fish-eye map out to elongation 'maxelo'
	     = 0: Mercator projection (similar to synoptic map)
	     < 0: Hammer-Aitoff projection
	     if absent then a Hammer-Aitoff map is drawn
   minelo	scalar; type: float
	     Erases plot inside of minelo
   /equator  if set, the 'horizontal' in the sky map is parallel to the
	     equatorial plane. By default the horizontal is along the ecliptic
   upto=upto scalar; type: integer; default: TimeUnit(/hour)
	     controls the length of the UT string plotted
   scale=scale	 scalar; type: float; default: 1.0
	     controls the overall size of the skymap relative to the plot window
   /galactic if set, add a line for the galactic plane

   point_sources=point_sources
	  array; type: sky_point_source structure
	     contains information about point sources to be overplotted
	     on the skymap. See vu_point_source.
   /point_names
	  if set, then the names of the point sources are plotted

   point_size=point_size
	  scalar or array[2]; controls the size of the circles used to plot the
	  point source position. The size is specified in radians or degrees
	  (depending on setting of /degrees).

	  point_size[0]: minimim size of circle.
	  point_size[1]: increment in circle size per unit of the function
	     value in skymap F.

	  point_size[1] is used to increase the circle size proportional to
	  the difference between the point source fnc value and the value in
	  the skymap F.

	  If point_size[1] is not set bad (and /point_onesize is NOT set)
	  then only sources with valid function values will be plotted.
	  (I.e. to plot only good sources with the same cirle size set
	  point_size[1] to zero.)

	  If point_size[1] is bad or omitted then /point_onesize is assumed set.

   /point_onesize
	  if set then all sources (including those with bad fnc values)
	  are plotted with the same size circle point_size[0].
	  This is useful to override the information stored
	  in 'point_sources' or in keyword element point_size[1].

	  If only IPS sources are plotted (i.e. if no skymap F is specified) then
	  setting /point_onesize will plot all source position with the same size.

   The following three keywords are clumsy to use. The idea is to control the orientation
   of the map (i.e. direction of origin, and tilt of horizontal on sky).
   vu_EarthSkymap uses these keywords to set up sky 'snapshots' and sky 'sweeps'.

   dabg   array[3]; type: float; default: [0,0,0]
	     (used by the projection functions FishEye, HammerAitoff and
	     MercatorProj, either directly in this procedure or indirectly in
	     ColorSkybox)

   zero_point	 scalar; type: float; default: 0.0
	     (used internally and passed to FishEye, HammerAitoff and MercatorProj)
	     Defines the longitude or RA of the center of the FishEye,HammerAitoff
	     or Mercator map.

   zero_phase	 scalar, or array with same structure as 'RA'; type: float; default: zero_point
	     (passed to ColorSkybox)
	     ColorSkybox uses this keyword to rearrange its first three arguments
	     (RA,DEC and fnc-values) to put zero_phase in the center of the map.
	     This modifies input arrays RA and DEC, but not F.

   For sky 'snapshots' zero_phase is the same as zero_point.
   For sky 'sweeps' zero_phase is a monotonic array with a value for each sweep, and
   the value of 'zero_point' (almost) exactly in the center of 'zero_phase'. Note that
   inconsistent settings of zero_point and zero_phase make an incorrect map.
 OUTPUTS:
 INCLUDE:
    @compile_opt.pro	  ; On error, return to caller
 CALLS: ***
	ARG_TIME, AngleRange, BadValue, ColorSkybox, CvSky, EarthSky3DLoc, EarthTransit3DLoc
	EulerRotate, FILEPATH, FishEye, GeographicInfo, GetColors [1], GetColors [2]
	GetColors [3], GetFileSpec, HammerAitoff, INTERPOL, IPS_params, InitVar
	IntegrateLOS, IsType, LOADCT, MercatorProj, NewcombSun, PlotCurve, REVERSE, STRETCH
	ThomsonRadialFilter, TimeGet, TimeSet, TimeString, TimeUnit, ToDegrees, ToRadians
	UBVCONST, UNIQ, UlyssesOrbit, VU_TYPE_SKY, WhatIs, anicenum, destroyvar, flt_read
	gridgen, reset_colors, set_page, vu_earthskymap, vu_get, vu_get_page, vu_getdata
	vu_gettime, vu_point_source, vu_thomson_hammer
 CALLED BY:
	GetColors [2], GetColors [3], allsky [1], allsky [2], allsky [3], allsky_f, smei_sky
	smei_zldsky, vu_earthskymap, vu_thomson_antifish, vu_thomson_hammer
 PROCEDURE:
 > Time UT is needed to calculate the location of equator and ecliptic
 > The ecliptic is drawn on an equatorial skymap and v.v
 > Longitude/RA is plotted increasing right-to-left across the map
   (as it is for a viewer at Earth looking up at the sky). For sun-centered maps
   this means that east is left and west is right. A mirror image of the map
   can be made by setting keyword /mirror.
 > The data range for the horizontal axis is -180,+180 degrees relative to
   'zero_point' as needed for the Hammer-Aitoff and fisheye projections. I.e.
   longitude/RA 'zero_point' will appear at the center of the map.
 MODIFICATION HISTORY:
   SEP-1999, Paul Hick (UCSD/CASS)
   FEB-2002, Paul Hick (UCSD/CASS)
     Added option to plot a sky map in Mercator projection by setting maxelo=0.
   APR-2002, Paul Hick (UCSD/CASS)
     Added /fill2edge keyword (passed to ColorSkybox)
   SEP-2003, Paul Hick (UCSD/CASS)
     Minor tweaking of labels to get Mercator projection to look better
     Added /galactic keyword.
   AUG-2004, Paul Hick (UCSD/CASS)
     Started adding some code to deal with Thomson scattering brightness
     (mainly for overplotting point sources).
     The time plotted at the top is now rounded instead of truncating
     to timeunit 'upto'.
   SEP-2004, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
     For fisheye plots point sources with outside maxelo are not plotted anymore
     Reworked the determination of the circle sizes for the point sources, and
     added some keywords to control them.


PlotEloTimeMap $SMEI/ucsd/sat/idl/toolbox/graphics/plotelotimemap.pro
[Previous] [Next]
 NAME:
	PlotEloTimeMap
 PURPOSE:
	Plot elongation - time map (J-map)
 CATEGORY:
	sat/idl/toolbox
 CALLING SEQUENCE:
	PRO PlotEloTimeMap, pa_angle, time_grid, elo_grid, F, $
	    degrees	= degrees	, $
	    noerase	= noerase	, $
	    breakval	= breakval	, $
	    basebreak	= basebreak	, $
	    logscale	= logscale	, $
	    charsize	= charsize	, $
	    title	= title 	, $
	    scale	= scale 	, $
	    format	= format	, $
	    _extra	= _extra	, $
	    silent	= silent	, $
	    goodcolor	= goodcolor	, $
	    badcolor	= badcolor	, $

	    pa_position = pa_position	, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $

	    body	= body		, $

	    position	= position	, $
	    legend	= legend	, $
	    compass	= compass	, $
	    max_dec	= max_dec	, $
	    ra_step	= ra_step	, $
	    dec_step	= dec_step	, $
	    naked	= naked
 INPUTS:
	pa_angle    scalar; type: float
			position angle
	time_grid   array[n]; type: time structure
			array of times
	elo_grid    array[m]; type: float
			array of solar elongations
	F	    array[n,m]; type: float
			array of function values in "time vs elo" map;
			each function value refers to a bin on the sky.
			The edges of the skybin are specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
	breakval    array[*]; type: integer or float
			levels between colors (passed to ColorSkybox)
			if not set, a set of break values is calculated
			equally spaced between minimum and maximum
	/logscale   if set, changes to logarithmic scale
	/degrees    if set, indicates that all angles are in degrees
			Default: radians.
	scale=scale scalar; type: float; default: 1.0
			controls the overall size of the skymap relative
			to the plot window

	/naked	    plots the skymap without any labeling or axes.

	goodcolor = goodcolor
		    scalar; type: integer; default: !d.n_colors-1
	badcolor  = badcolor
		    scalar; type: integer; default: !p.color

	/compass
	compass=compass
		    /compass will add label 'E' to left, and 'W' to
			right side of plot. To customize labeling specify
			2-element string (i.e. /compass is the same as
			compass=['E','W'])
	sn_position=sn_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of South/North
			labels. Units are percentages of the window size.
	we_position=we_position
		    array[4]; type: real
			Pairs of x,y coordinates for shifts of East/West
			labels.
	pa_position=pa_position
		    array[2]; type: real
			x,y coordinates for shifts of position angle label

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
	@vu_fnc_include.pro	;
 CALLS: ***
	AngleRange, BadValue, ColorEloTimeBox, CvSky, FishEye, GetColors [1], GetColors [2]
	GetColors [3], HammerAitoff, INTERPOL, InitVar, IsType, MEAN, MercatorProj, PlotCurve
	PlotUserstring, SuperArray, TimeGet, TimeSet, TimeXAxis, ToDegrees, ToRadians
	anicenum, big_eph, gridgen, sphere_distance
 CALLED BY:
	vu_elotime
 PROCEDURE:
 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS)


PlotPlanarCut $SMEI/ucsd/sat/idl/toolbox/graphics/plotplanarcut.pro
[Previous] [Next]
 NAME:
	PlotPlanarCut
 PURPOSE:
	Plot map of planar cut through sun-centered volume
 CATEGORY:
	sat/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO PlotPlanarCut, zz, ut=ut	, $
	    radius	= radius	, $
	    euler_angles= euler_angles	, $
	    degrees	= degrees	, $
	    euler_info	= euler_info	, $
	    breakval	= breakval	, $
	    title	= title 	, $
	    upto	= upto		, $
	    body	= body		, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $
	    _extra=_extra
 INPUTS:
	zz		array[n,n]; type: float
			    function value on disk
	ut=ut		array[1]; type: time structure
			    UT time used for ephemeris calculation
 OPTIONAL INPUT PARAMETERS:
	upto=upto	scalar; type: integer; default: none
			    return value of TimeUnit function.
			    The 'ut' time is plotted in the upper right
			    corner using TimeGet. The 'upto' keyword
			    determines at which time unit the string
			    is terminated.
	radius=radius	scalar; type: float; default: 1.0
			    radius of circular planar cut (in AU)
	body=body	scalar or array; type: string
			    names of bodies to be plotted
			    If trailing char is '&'
			    then the orbit is also plotted
	euler_angles=euler_angles
	/degrees	if set, angles are in degrees
			    default is radians
	euler_info=euler_info
	title=title	scalar; type: string
			    string plotted in lower-left corner
	breakval=breakval
			array; type: integer or float
			    contour levels passed to GetColors

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

	_extra=_extra	additional plot keywords
 OUTPUTS:
	(plot)
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	EulerRotate, GetColors [1], GetColors [2], GetColors [3], InitVar, IsType
	PlotUserstring, REVERSE, TimeGet, big_body, big_eph, big_orbit, gridgen, jpl_body
	mpc_body, setup3d, usno_body
 CALLED BY:
	vu_planarcut
 PROCEDURE:
	The appearance of the map is controlled by specifying
	plot keywords (passed here through the _extra keyword):

	Control character size with keyword charsize
	Control character thickness with keyword charthick
	Control size of body symbol with keyword symsize
	Control thickness of orbit with keyword thick
 MODIFICATION HISTORY:
	JUN-2006, Paul Hick (UCSD/CASS)
	OCT-2006, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Replaced jpl_eph and jpl_orbit calls by big_eph
	    and big_orbit calls.


PlotPolarSkymap $SMEI/ucsd/sat/idl/toolbox/graphics/plotpolarskymap.pro
[Previous] [Next]
 NAME:
	PlotPolarSkymap
 PURPOSE:
	Plot sky map in polar projection, with locations of point sources overplotted (optional)
 CATEGORY:
	gen/idl/graphics
 CALLING SEQUENCE:
	PRO PlotPolarSkymap, UT, cosRA, sinRA, F,   $
	    equator	= equator   , $
	    geolng	= geolng    , $
	    degrees	= degrees   , $
	    breakval	= BreakVal  , $
	    logscale	= logscale  , $
	    charsize	= charsize  , $
	    title	= title     , $
	    upto	= upto	    , $
	    scale	= scale     , $
	    minelo	= minelo    , $
	    zero_point	= zero_point, $
	    zero_phase	= zero_phase, $
	    dabg	= dabg	    , $
	    format	= format    , $
	    fill2edge	= fill2edge , $
	    _extra	= _extra    , $
	    galactic	= galactic  , $
	    silent	= silent    , $

	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $

	    point_sources=point_sources,$
	    point_names = point_names  ,$
	    point_size	= point_size   ,$
	    point_onesize=point_onesize,$

	    mirror	= mirror    , $
	    noerase	= noerase   , $
	    xrange	= xrange    , $
	    yrange	= yrange    , $
	    position	= position  , $
	    legend	= legend    , $
	    dec_step	= dec_step  , $
	    ra_step	= ra_step   , $

	    ra_position = ra_position, $
	    naked	= naked
 INPUTS:
	UT	    scalar; type: standard time structure
			time; determines position of Sun in the sky
	cosRA	    array[n]; type: float
		    +/- (90-DEC)*cos(RA)
			array of ecliptic longitudes or right ascensions
			(if /equator set) in the range [-180,+180]??NOT REALLY??
	sinRA	    array[m]; type: float
		    +/- (90-DEC)*sin(RA)
			array of ecliptic latitudes or declinations
			(if /equator is set) in the range [-90.90]
	F	    array[n,m]; type: float
			array of function values in sky map; each function value
			refers to bin on the sky. The edges of the skybin are
			specified in RA and DEC
 OPTIONAL INPUT PARAMETERS:
	breakval    array[*]; type: integer or float
			levels between colors (passed to ColorSkybox)
			if not set, a set of break values is calculated
			equally spaced between minimum and maximum
	/logscale   if set, changes to logarithmic scale
	/degrees    if set, indicates that all angles are in degrees
			Default: radians.
	minelo	    scalar; type: float
			Erases plot inside of minelo
	/equator    if set, the 'horizontal' in the sky map is parallel to the
			equatorial plane. By default the horizontal is along the ecliptic
	upto=upto   scalar; type: integer; default: TimeUnit(/hour)
			controls the length of the UT string plotted
	scale=scale scalar; type: float; default: 1.0
			controls the overall size of the skymap relative to the plot window
	/galactic   if set, add a line for the galactic plane

	/naked	    if set, then plot skymap without labeling and axes.

	point_sources=point_sources
		    array; type: sky_point_source structure
			contains information about point sources to be overplotted
			on the skymap. See vu_point_source.
	/point_names
		    if set, then the names of the point sources are plotted

	point_size=point_size
		    scalar or array[2]; controls the size of the circles used to plot the
		    point source position. The size is specified in radians or degrees
		    (depending on setting of /degrees).

		    point_size[0]: minimim size of circle.
		    point_size[1]: increment in circle size per unit of the function
			value in skymap F.

		    point_size[1] is used to increase the circle size proportional to
		    the difference between the point source fnc value and the value in
		    the skymap F.

		    If point_size[1] is not set bad (and /point_onesize is NOT set)
		    then only sources with valid function values will be plotted.
		    (I.e. to plot only good sources with the same cirle size set
		    point_size[1] to zero.)

		    If point_size[1] is bad or omitted then /point_onesize is assumed set.

	/point_onesize
		    if set then all sources (including those with bad fnc values)
		    are plotted with the same size circle point_size[0].
		    This is useful to override the information stored
		    in 'point_sources' or in keyword element point_size[1].

		    If only IPS sources are plotted (i.e. if no skymap F is specified) then
		    setting /point_onesize will plot all source position with the same size.

	The following three keywords are clumsy to use. The idea is to control the orientation
	of the map (i.e. direction of origin, and tilt of horizontal on sky).
	vu_earthskymap uses these keywords to set up sky 'snapshots' and sky 'sweeps'.

	dabg	    array[3]; type: float; default: [0,0,0]
			(used by the projection functions FishEye, HammerAitoff and
			MercatorProj, either directly in this procedure or indirectly in
			ColorSkybox)

	zero_point  scalar; type: float; default: 0.0
			(used internally and passed to FishEye, HammerAitoff and MercatorProj)
			Defines the longitude or RA of the origin.

	zero_phase  scalar, or array with same structure as 'RA'; type: float; default: zero_point
			(passed to ColorSkybox)
			ColorSkybox uses this keyword to rearrange its first three arguments
			(RA,DEC and fnc-values) to put zero_phase in the center of the map.
			This modifies input arrays RA and DEC, but not F.

	For sky 'snapshots' zero_phase is the same as zero_point.
	For sky 'sweeps' zero_phase is a monotonic array with a value for each sweep, and
	the value of 'zero_point' (almost) exactly in the center of 'zero_phase'. Note that
	inconsistent settings of zero_point and zero_phase make an incorrect map.

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	    ; On error, return to caller
 CALLS: ***
	AngleRange, BadValue, ColorSkybox, CvSky, FishEye, GeographicInfo, GetColors [1]
	GetColors [2], GetColors [3], HammerAitoff, INTERPOL, InitVar, IsType, MercatorProj
	PlotCurve, PlotUserstring, TimeGet, TimeUnit, ToDegrees, ToRadians, anicenum, big_eph
	gridgen, jpl_body, vu_point_source
 CALLED BY:
	smei_sky
 PROCEDURE:
 >	Time UT is needed to calculate the location of equator and ecliptic
 >	The ecliptic is drawn on an equatorial skymap and v.v
 MODIFICATION HISTORY:
	SEP-1999, Paul Hick (UCSD/CASS)
	FEB-2002, Paul Hick (UCSD/CASS)
	    Added option to plot a sky map in Mercator projection by setting maxelo=0.
	APR-2002, Paul Hick (UCSD/CASS)
	    Added /fill2edge keyword (passed to ColorSkybox)
	SEP-2003, Paul Hick (UCSD/CASS)
	    Minor tweaking of labels to get Mercator projection to look better
	    Added /galactic keyword.
	AUG-2004, Paul Hick (UCSD/CASS)
	    Started adding some code to deal with Thomson scattering brightness
	    (mainly for overplotting point sources).
	    The time plotted at the top is now rounded instead of truncating
	    to timeunit 'upto'.
	SEP-2004, Paul Hick (UCSD/CASS)
	    For fisheye plots point sources with outside maxelo are not plotted anymore
	    Reworked the determination of the circle sizes for the point sources, and
	    added some keywords to control them.
	OCT-2006, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Replaced NewcombSun by big_eph calls


PlotPrep $SMEI/ucsd/gen/idl/toolbox/graphics/plotprep.pro
[Previous] [Next]
 NAME:
	PlotPrep
 PURPOSE:
 CALLING SEQUENCE:
	FUNCTION PlotPrep, xin, yin, nvalid, $

	    oplotx	= oplotx     , $
	    newyaxis	= newyaxis   , $

	    yaxis	= yaxis      , $
	    xrange	= xrange     , $
	    yrange	= yrange     , $
	    ystyle	= ystyle     , $
	    ynozero	= ynozero    , $
	    ylog	= ylog	     , $
	    changecolor = changecolor, $
	    ycolor	= ycolor     , $
	    silent	= silent     , $
	    _extra	= _extra     , $

	    ; Output

	    xpnt	= xpnt	     , $
	    ypnt	= ypnt	     , $
	    npnt	= npnt
 INPUTS:
	xin	    one-dimensional abcissa array
		    To plot a time axis (using TimeXAxis) xin must be
		    an array of time structures, or a string array that
		    is converted to time structures with TimeSet.
	yin	    one-dimensional ordinate array
		    must have the same size as xin
	nvalid	    one-dimensional array identifying the array elements
		    to be plotted as:
		    - an array of indices e.g. [0,1,2,7,8,9,10]
		    - a boolean array (containing only values 0 or 1)
			of same size as xin and yin, e.g. [1,1,1,0,0,0,0,1,1,1,1]
		    if nvalid is absent, all finite ordinate values are plotted
 OPTIONAL INPUT PARAMETERS:
	/oplotx     if not set, then a new plot (with a new x-axis) is started)
		    (implicitly /newyaxis is set and yaxis=-1, i.e. a y-axis
		    will be drawn on the left)
		    if set, then the arrays are overplotted on a previous plot
		    (the keywords /newyaxis and yaxis=yaxis can be used to add
		    additional y axes, if necessary)
	/newyaxis   adds a new yaxis
		    (if /oplotx is NOT set, then /newyaxis is assumed set)
	yaxis=yaxis controls the position of a new y axis; yaxis is used
		    only if /newaxis is set
		    yaxis=-1 : y-axis on left (default)
		    yaxis=0  : y-axis on right
		    0<yaxis<1: y-axis is placed in the right margin
			(if this is used then ymargin must be made big enough
			to hold the extra y axis).

	silent=silent
		    suppresses informational messages
 OUTPUTS:
	Result	    number of points to be plotted (= n_elements(npnt))
 OPTIONAL OUTPUT PARAMETERS:
	xpnt	    same as xin; may have been coverted to a time array
	ypnt	    same as yin
	npnt	    indices into xpnt,ypnt with valid ypnt values
 INCLUDE:
	@compile_opt.pro	    ; On error, return to caller
 CALLS: ***
	InitVar, IsTime, IsType, TimeOp, TimeSet, TimeXAxis
 CALLED BY:
	PlotBars, PlotCurves
 COMMON BLOCKS:
	common TimeScale, torigin, trange, tunit, texact	; Set by TimeXAxis
 MODIFICATION HISTORY:
	NOV-2010, Paul Hick (UCSD/CASS)
	    Extracted from PlotCurve


PlotSolarDisk $SMEI/ucsd/sat/idl/toolbox/graphics/plotsolardisk.pro
[Previous] [Next]
 NAME:
	PlotSolarDisk
 PURPOSE:
	Plot map of solar disk
 CATEGORY:
 CALLING SEQUENCE:
	PRO PlotSolarDisk, zz, ut=ut,	$
	    radius  = radius	, $
	    diameter= diameter	, $
	    breakval= breakval	, $
	    xysize  = xysize	, $
	    title   = title	, $
	    upto    = upto	, $
	    rotate  = rotate	, $
	    earth   = earth	, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $
	    _extra  = _extra
 INPUTS:
	zz		array[diameter,diameter]; type: float
			    function value on disk
 OPTIONAL INPUT PARAMETERS:
	rotate=rotate	array[3,*]
			    sets of rotations needed to rotate
			    from x-y-z to heliographic coordinates
	ut = ut
	diameter=diameter
			scalar; type: integer; default: 0.8*!d.x_size
			    diameter of disk in pixels

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.

 OUTPUTS:
 OPTIONAL OUTPUT PARAMETERS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	CvT3d, GetColors [1], GetColors [2], GetColors [3], InitVar, IsType, PlotUserstring
	REVERSE, TimeGet, big_eph, gridgen, jpl_body, plot3darc, plot3dtext, setup3d
	vectorproduct
 CALLED BY:
	vu_solardisk
 SEE ALSO:
 PROCEDURE:
 MODIFICATION HISTORY:
	AUG-2002, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PlotSphereCut $SMEI/ucsd/sat/idl/toolbox/graphics/plotspherecut.pro
[Previous] [Next]
 NAME:
	PlotSphereCut
 PURPOSE:
	Plot lng-lat map of sun-centered sphere
 CATEGORY:
	sat/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO PlotSphereCut, Map, ut=ut	, $
	    radius	= radius	, $
	    euler_angles= euler_angles	, $
	    degrees	= degrees	, $
	    euler_info	= euler_info	, $
	    breakval	= breakval	, $
	    title	= title 	, $
	    upto	= upto		, $
	    body	= body		, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $

	    plotcenter	= plotcenter	, $
	    plotsize	= plotsize	, $
	    grid	= grid		, $

	    _extra=_extra
 INPUTS:
	zz		array[n,n]; type: float
			    function value on disk
	ut=ut		array[1]; type: time structure
			    UT time used for ephemeris calculation
 OPTIONAL INPUT PARAMETERS:
	upto=upto	scalar; type: integer; default: none
			    return value of TimeUnit function.
			    The 'ut' time is plotted in the upper right
			    corner using TimeGet. The 'upto' keyword
			    determines at which time unit the string
			    is terminated.
	radius=radius	scalar; type: float; default: 1.0
			    radius of sphere (in AU)
	euler_angles=euler_angles
	/degrees	if set, angles are in degrees
			    default is radians
	euler_info=euler_info
	title=title	scalar; type: string
			    string plotted in lower-left corner
	breakval=breakval
			array; type: integer or float
			    contour levels passed to GetColors

	user_string=user_string
			scalar or array; type: string
			    User specified string(s) to be plotted
	user_position=user_position
			array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			    Start position(s) of user string(s) in normal
			    coordinates. The default allows plotting of two
			    user-defined strings in upper-left and lower-right
			    corners.

	_extra=_extra	additional plot keywords
 OUTPUTS:
	(plot)
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	CONGRID, GetColors [1], GetColors [2], GetColors [3], InitVar, IsType
	PlotUserstring, REVERSE, TimeGet, ToDegrees, ToRadians, gridfill, gridgen
 CALLED BY:
	vu_spherecut
 PROCEDURE:
	The appearance of the map is controlled by specifying
	plot keywords (passed here through the _extra keyword):

	Control character size with keyword charsize
	Control character thickness with keyword charthick
	Control size of body symbol with keyword symsize
	Control thickness of orbit with keyword thick
 MODIFICATION HISTORY:
	MAY-2010, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PlotSynopticMap $SMEI/ucsd/sat/idl/toolbox/graphics/plotsynopticmap.pro
[Previous] [Next]
 NAME:
	PlotSynopticMap
 PURPOSE:
	Plot synoptic map
 CATEGORY:
	WWW: graphics
 CALLING SEQUENCE:
	PRO PlotSynopticMap, XCplot, Map, $
	    XCmap   = XCmap	, $
	    YLmap   = YLmap	, $
	    YLshow  = YLshow	, $
	    YLplot  = YLplot	, $
	    degrees = degrees	, $
	    breakval= breakval	, $
	    plotcenter=plotcenter,$
	    plotsize= plotsize	, $
	    fill    = fill	, $
	    grid    = grid	, $
	    draw_contour=draw_contour, $
	    timeaxis= timeaxis	, $
	    user_position=user_position , $
	    user_align	= user_align	, $
	    user_string = user_string	, $
	    _extra  = _extra
 INPUTS:
	XCplot		scalar or array[2]; type: float
			    start and end Carrington variable to be displayed
			    if a scalar is specified this is used as start value, and the end
			    value is set to the start value, plus one (i.e. one rotation
			    is assumed)
	Map		2D array; any type

 OPTIONAL INPUT PARAMETERS:
	xcmap=XCmap	array[2]; type: float; default: XCplot
			    range of Carrington variable of input array Map
	ylmap=YLmap	array[2]; type: float; default: [-90,90] degrees
			    latitude range of input array Map
	ylplot=YLplot	array[2]; type: float: default: ylmap
			    latitude range covered by vertical axis
	ylshow=YLshow	array[2]; type: float: default: ylplot
			    latitude range of input map actually shown on plot
	/degrees	scalar; type: integer; default:0 (radians)
			    if set YLmap should be in degrees
	plotcenter=plotcenter
			array[2]; type: integer; default: [!d.x_size,!d.y_size]/2
			    pixel coordinates for center of map
	plotsize=plotsize
			array; type: integer; default: 0.8*plotcenter[0]
			    size of map in pixels

	breakval=breakval
			array[*]; type: float
			    contour levels used to plot map
	/draw_contour	if set then the IDL 'contour' function is used to plot
			    the map instead of the 'tv' function

	/fill		if set then 'map_grid' is called to fill in bad values
			    before plotting the map
	/grid		if set then the grid of the input map is marked by
			    putting crosses at the corners of grid squares.
	timeaxis=timeaxis   if set, adds a time axis at the top of the map, specifying the time at
			which the corresponding heliographic longitude crossed the
			central meridian on the solar disk

	user_string=user_string
		    scalar or array; type: string
			User specified string(s) to be plotted
	user_position=user_position
		    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.
 OUTPUTS:
	(none)
 OPTIONAL OUTPUT PARAMETERS:
 INCLUDE:
	@compile_opt.pro	    ; On error, return to caller
 CALLS: ***
	CONGRID, Carrington, GetColors [1], GetColors [2], GetColors [3], InitVar, IsType
	MEAN, PlotUserstring, REVERSE, TimeUnit, TimeXAxis, ToDegrees, ToRadians, gridfill
	gridgen
 CALLED BY:
	nso_fe_plot, show_wso, vu_synopticmap
 PROCEDURE:
 MODIFICATION HISTORY:
	APR-1999, Paul Hick (UCSD/CASS)
	FEB-2002, Paul Hick (UCSD/CASS)
	    Added xsize and ysize keywords to 'tv' call. This is needed for
	    devices with scalable pixels, such as PS.
	JUL-2002, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
	    Added 'timeaxis' keyword to add a time axis
	    at top of map. This was always done before.


PlotUserstring $SMEI/ucsd/sat/idl/toolbox/graphics/plotuserstring.pro
[Previous] [Next]
 NAME:
	PlotUserstring
 PURPOSE:
	Add strings to maps
 CATEGORY:
	sat/idl/toolbox/graphics
 CALLING SEQUENCE:
	PRO PlotUserstring, str, pos, align=align, _extra=_extra
 INPUTS:
	str	    scalar or array; type: string
			User specified string(s) to be plotted
	pos	    array[2,n]; type: real; default: [[0.05,0.95],[0.80,0.05]]
			Start position(s) of user string(s) in normal
			coordinates. The default allows plotting of two
			user-defined strings in upper-left and lower-right
			corners.
 OPTIONAL INPUT PARAMETERS:
 OUTPUTS:
 INCLUDE:
	@compile_opt.pro	    ; On error, return to caller
 CALLS: ***
	InitVar, IsType
 CALLED BY:
	PlotCoronagraph, PlotEarthSkymap [1], PlotEloTimeMap, PlotPlanarCut
	PlotPolarSkymap, PlotSolarDisk, PlotSphereCut, PlotSynopticMap
 PROCEDURE:
 MODIFICATION HISTORY:
	JUL-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PRO bold $SMEI/user/pphick/idl/bol.pro
[Previous] [Next]
 NAME:
	PRO bol,d
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	AngleRange, AngleUnits, ArrayLocation, BOL, ELONGATION, HIST_2D, IsType, MEAN, REVERSE
	STDDEV, SuperArray, WhatIs, boost, cvsmei, destroyvar, smei_i2m, smei_star_list
	smei_star_readpnt, view


PRO bolstrip $SMEI/user/pphick/idl/bolstrip.pro
[Previous] [Next]
 NAME:
	PRO bolstrip
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	BOLSTRIP, REVERSE, WhatIs, boost, smei_star_info, txt_read


pro ccd $SMEI/user/pphick/idl/ccd.pro
[Previous] [Next]
 NAME:
	pro ccd
 INCLUDE:
	@compile_opt.pro
COMMON:
common	CCDInfo
nCCD
rOrig
rFOV1
rFOV2
rAnchor
 CALLS: ***
	ArrayLocation, CCD, CCD2SKY, CV_COORD, FILEPATH, flt_read


PRO symbol_soup $SMEI/user/pphick/idl/symbol_soup.pro
[Previous] [Next]
 NAME:
	PRO symbol_soup
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	FILEPATH, SYMBOL_SOUP


PRO test_magnify $SMEI/user/pphick/idl/test_magnify.pro
[Previous] [Next]
 NAME:
	PRO test_magnify
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	ArrayLocation, MagnifyArray, TEST_MAGNIFY, WhatIs, twin, view


PROFREE $SMEI/user/pphick/idl/cmsvlib/profree.pro
[Previous] [Next]
 NAME:
   PROFREE

 AUTHOR:
   Craig B. Markwardt, NASA/GSFC Code 662, Greenbelt, MD 20770
   craigm@lheamail.gsfc.nasa.gov

 PURPOSE:
   Free the pointers associated with an PRODIS abstract syntax tree

 CALLING SEQUENCE:
   PROFREE, TREE

 DESCRIPTION:

   PROFREE frees the memory and pointers associated with an abstract
   syntax tree, as returned by PRODIS.	Users should use this
   procedure when they are finished with an abstract syntax tree and
   want to release its resources.  The procedure frees all pointers
   in the tree recursively.

 INPUTS:

   TREE - the abstract syntax tree to be freed.  Upon return the
	  contents of TREE will be undefined.


 SEE ALSO:
	CMSAVEDIR, CMSVLIB, PRODIS, PROREND
 MODIFICATION HISTORY:
   Written, 2000-2002, CM
   Documented, 19 Mar 2002, CM


 $Id: profree.pro,v 1.3 2002/03/19 21:45:02 craigm Exp $


projfig $SMEI/user/pphick/idl/figures/projfig.pro
[Previous] [Next]
 NAME:
	projfig
 CALLING SEQUENCE:
	pro projfig, figure, hammer=hammer, fish=fish, zbuffer=zbuffer
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	CV_COORD, FILEPATH, FishEye, HammerAitoff, InitVar, LOADCT, REVERSE, WRITE_GIF, gridgen
	mk_flick, plot3darc, plot3dline, plot3dtext, setup3d, twin, vectorproduct


PROREND $SMEI/user/pphick/idl/cmsvlib/prorend.pro
[Previous] [Next]
 NAME:
   PROREND

 AUTHOR:
   Craig B. Markwardt, NASA/GSFC Code 662, Greenbelt, MD 20770
   craigm@lheamail.gsfc.nasa.gov

 PURPOSE:
   Render a PRODIS abstract syntax tree into IDL Language Text

 CALLING SEQUENCE:
   PROREND, TREE, TEXT, [ /INIT ]

 DESCRIPTION:

   PROREND converts an abstract syntax tree as returned by PRODIS,
   into a human-readable form, written in the IDL programming
   language.  The abstract syntax tree format is a set of linked data
   structures, and is derived from the raw data on disk.  The human
   readable form is returned as an array of strings that can be
   printed to the console or a file.

   The abstract syntax tree is generated by PRODIS, an external
   procedure in the same library.  The standard approach is to use
   the following steps:

       1. Use PRODIS to convert raw bytes to abstract syntax tree
       2. Use PROREND to convert abstract syntax tree to IDL language

   The external routine PROTRANS does the end-to-end conversion steps
   of both PRODIS and PROREND for you.

   At the moment there is relatively little flexibility in how the
   IDL code is rendered to text.  For example, all reserved keywords
   and variables appear in upper-case letters, and array indexing
   syntax is expressed with round ()'s instead of square []'s.
   Suggestions on how to achieve this are solicited.

   PROREND does not free the TREE structure.  The user is responsible
   to do this using the PROFREE procedure.


 COMPATIBILITY:

   -- File Format --

   PROREND accepts any tree provided by PRODIS.  PRODIS cannot
   examine compressed save files.  It is able to read and translate
   SAVE files produced by IDL 4, and IDL versions 5.0 through 5.5.
   The output of PROREND should be compatible with IDL 4 and 5.

   This procedure is part of the CMSVLIB SAVE library for IDL by
   Craig Markwardt.  You must have the full CMSVLIB core package
   installed in order for this procedure to function properly.

 INPUTS:

   TREE - the abstract syntax tree, as returned by PRODIS.  This
	  structure is unmodified by PROREND.

   TEXT - upon output, the IDL code is placed in as an array of
	  strings in TEXT.  By default, any new IDL code will be
	  *appended* to TEXT.  Use the /INIT keyword to overwrite the
	  existing contents of TEXT.


 KEYWORDS:

   INIT - if set, then overwrite the TEXT array with the new IDL
	  code.  By default (INIT not set), any new IDL code is
	  *appended* to TEXT.

 EXAMPLE:

   This example compiles a test function, saves it to a file called
   test_pro.sav, and then disassembles the save file into a syntax
   tree using PRODIS.  Finally, the syntax tree is converted to IDL
   text, which is printed to the console.

     IDL> .comp
     - pro test_pro, x
     -	 x = x + 1
     -	 return
     - end
     % Compiled module: TEST_PRO.
     IDL> save, 'test_pro', /routine, file='test_pro.sav'
     IDL> prodis, 'test_pro.sav', prodecl, tree
     IDL> prorend, tree, text
     IDL> print, text, format='(A)'
     PRO TEST_PRO, X
       ;; Beginning of code
       X = X+1
       RETURN
     END


 CALLS: ***
	PRN_ARRAY, PRN_ASSIGN, PRN_CASE, PRN_FOR, PRN_IF, PRN_ONIOERROR, PRN_OPN, PRN_PARSE
	PRN_PDEREF, PRN_PROCALL, PRN_PUSH, PRN_RETURN, PRN_STRCAT, PRN_STRUCT, PRN_STRUCTREF
	PRN_SUBSCRIPT, PRN_TRICOND, PRN_UBOP, PRN_WHILE
 SEE ALSO:
	CMSAVEDIR, CMSVLIB, PRODIS, PROREND
 MODIFICATION HISTORY:
   Written, 2000-2002, CM
   Documented, 19 Mar 2002, CM
   Added PRN_STRCAT, to avoid an internal library function, 22 Mar
     2002, CM


 $Id: prorend.pro,v 1.13 2002/03/22 22:01:11 craigm Exp $


psfn $SMEI/user/pphick/idl/psfn.pro
[Previous] [Next]
 NAME:
	psfn
 CALLING SEQUENCE:
	PRO psfn
 INCLUDE:
	@compile_opt.pro
 CALLS: ***
	FILEPATH, GetFileSpec, READFITS, WRITEFITS, smei_filename, smei_getfile


put_logo $SMEI/ucsd/sat/idl/util/put_logo.pro
[Previous] [Next]
 NAME:
	put_logo
 PURPOSE:
	Adds logo to image
 CATEGORY:
	sat/idl/util
 CALLING SEQUENCE:
	PRO put_logo, img, logo=logo, match_background=match_background
 INPUTS:
 OPTIONAL INPUT PARAMETERS:
 OUTPUTS:
 OPTIONAL OUTPUT PARAMETERS:
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
 CALLS: ***
	InitVar, IsType, SubArray, SuperArray, img_read
 CALLED BY:
	get_page
 PROCEDURE:
	Crappy
 MODIFICATION HISTORY:
	OCT-2006, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


PutFileSpec $SMEI/ucsd/gen/idl/toolbox/files/putfilespec.pro
[Previous] [Next]
 NAME:
	PutFileSpec
 PURPOSE:
	Updates internal data originally set up by SetFileSpec
 CATEGORY:
	I/O, string manipulation
 CALLING SEQUENCE:
	PRO PutFileSpec, FileSpec, $
	    from    = From  , $
	    upto    = Upto  , $
	    part    = Part  , $
	    parse   = Parse , $
	    strict  = strict
 INPUTS:
	FileSpec    string scalar of array with file names
		If it is an array it should have the same
		# elements as the internal data.
 OPTIONAL INPUT PARAMETERS:
	From, UpTo  string scalars
		Any of the following six strings can be used:
		'NODE','DEVICE','DIRECTORY','NAME','TYPE','VERSION'
		The input is case-insensitive
		Only a unique starting substring has to be specified
		If From is not specified, From='NODE' is assumed
		If UpTo is not specified, UpTo='VERSION' is assumed
	/parse	    if set, the filenames are parsed before adding them
		to the internal data (/parse is passed to SetFileSpec;
		see that procedure for more information about parsing).
 OUTPUTS:
	None (the modified internal data are accessed by GetFileSpec)
 INCLUDE:
	@compile_opt.pro	; On error, return to caller
	@filespec_common.pro	; Common block with array File and Parts
 CALLS: ***
	InitVar, SetFileSpec, strposn
 CALLED BY:
	vu_extract, vu_vox_write
 SIDE EFFECTS:
	If FileSpec is an array it must have the same size as the internal data.
 PROCEDURE:
	FileSpec is passed through SetFileSpec (with the /nosave keyword set so
	the internal data are not modified) to decompose into separate file
	parts. The relevant part (as identified from the From and UpTo strings)
	are then used to overwrite (part of) the internal data.
 MODIFICATION HISTORY:
	DEC-1997, Paul Hick (UCSD/CASS; pphick@ucsd.edu)