JD_SYNC $SMEI/for/lib/jd_sync.f
[Previous] [Next]
 NAME:
	JD_SYNC
 PURPOSE:
 CATEGORY:
 CALLING SEQUENCE:
	subroutine JD_SYNC(IJD,EARTH,bForeCast,XCbeg,XCtst,JDref,JDcntr,XCEarth,LatEarth,nCar,JDCar)
 INPUTS:
 OUTPUTS:
 CALLS: ***
	ECLIPTIC_HELIOGRAPHIC, FLINT8, Julian, SunNewcomb, XMAP_SC_POS
 INCLUDE:
	include		'sun.h'
 EXTERNAL:
	external	EARTH
 PROCEDURE:
 MODIFICATION HISTORY:
	JUN-1995, Paul Hick (UCSD)


jpl_close $SMEI/ucsd/gen/for/lib/ephem/jpl_state.f
[Previous] [Next]
 NAME:
	jpl_close
 PURPOSE:
	Closes ephemeris file
 CALLING SEQUENCE:
	entry jpl_close()
 CALLS: ***
	CvI4, CvR8, Say, bOSFindClose, bOpenFile, iFilePath, iFreeLun, iSearch, jpl_inside
	jpl_interp
 PROCEDURE:
	Read explanation in jpl_eph2. Currently this function is useless.
 MODIFICATION HISTORY:
	FEB-2005, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


jpl_eph $SMEI/ucsd/gen/for/lib/ephem/jpl_eph.f
[Previous] [Next]
 NAME:
	jpl_eph
 PURPOSE:
	Read the JPL planetary ephemeris and gives position and velocity
	of body 'ntarg' with respect to body 'ncent'.
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	logical function jpl_eph(jd,ntarg,ncent,rrd,bKm,bBary)
 INPUTS:
	jd	double precision	Ephemeris time specified as Julian day.

	For other input arguments (ntarg, ncent, bKm and bBary)
	see jpl_eph2.
 OUTPUTS:
	rrd(6)	double precision	position vector (see jpl_eph)
	jpl_eph	logical			status indicator (see jpl_eph)
 CALLS: ***
	jpl_eph2
 CALLED BY:
	jpl_test
 EXAMPLE:
	logical          bOK
	logical          jpl_eph
	double precision jd
	double precision rrd(6)

	ncent = 3  ! Earth at origin
	ntarg = 10 ! Moon
	bOK = jpl_eph(jd,ntarg,ncent,rrd,.FALSE.,.FALSE.)

	! The ephemeris fails only if the JPL ephemeris files are not
	! found (probably means environment variable $EPHEM is not defined),
	! or if the input jd is earlier than 1950 or later than 2050 (probably
	! means jd was calculated wrong).
	
	if ( .not. bOK ) stop 'bad ephemeris'
	
	! Switch to single precision
	
	x = rrd(1)
	y = rrd(2)
	z = rrd(3)
	
	! RA, dec in degrees
	
	ra  = atan2d( y, x )
	dec = atan2d( z, sqrt( x*x+y*y ) )
 PROCEDURE:
	See jpl_eph2 for full documentation.
	jpl_eph is just a wrapper for jpl_eph2.
	The only difference is in the first argument (the time).
 MODIFICATION HISTORY:


jpl_eph2 $SMEI/ucsd/gen/for/lib/ephem/jpl_eph2.f
[Previous] [Next]
 NAME:
	jpl_eph2
 PURPOSE:
	Read the JPL planetary ephemeris and gives position and velocity
	of body 'ntarg' with respect to body 'ncent'.
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	logical function jpl_eph2(et,ntarg_,ncent_,rrd,bKm,bBary)
 INPUTS:
	et(2)	double precision	Ephemeris time specified as Julian day.
			A. put entire epoch in et(1) and set et(2)=0 (equivalent to jpl_eph)
			B. for maximum interpolatin accuracy, set et(1) to the most recent midnight
			   at or before the interpolation time, and put the remaining fraction in et(2)
			C. pick a fixed epoch for et(1) and put the elapsed time since that
			   epoch in et(2)
	ntarg	integer	number of the body whose position and velocity are needed
	ncent	integer	number of the body used as the origin
			The numbering convention for NTARG and NCENT is:
			0 = SUN (same as 11)
			1 = MERCURY		 9 = PLUTO
			2 = VENUS		10 = MOON
			3 = EARTH		11 = SUN
			4 = MARS		12 = NUTATIONS (LONGITUDE AND OBLIQ)
			5 = JUPITER		13 = LIBRATIONS, IF ON EPH FILE
			6 = SATURN		14 = SOLAR-SYSTEM BARYCENTER
			7 = URANUS		15 = EARTH-MOON BARYCENTER
			8 = NEPTUNE		
	(For nutations and librations used NTARG=12 and 13 respectively. NCENT is ignored)

	bKm	logical	flag setting the units of the output (default: .FALSE.)
			bKm	= .TRUE. : KM and KM/SEC
		    		= .FALSE.: AU and AU/DAY
			bKm determines the time unit for nutations and librations
				The angles are always in radians.
	bBary	logical	flag defining the output center (default: .FALSE.)
			(affects only the 9 planets)
			bBary	= .TRUE. : center is solar system barycenter
				= .FALSE.: center is Sun
 OUTPUTS:
	rrd(6)	double precision
			Position (AU or km) and velocity (AU/day or km/s) of NTARG with
			respect to NCENT
			For librations the units are radians and radians/day
			For nutations the first four will be set (units of radians and
			radians/day).
	jpl_eph2 logical	return value of call to jpl_init.
				will be .FALSE. if input time was outside range of ephemeris
				file or if there was a read error. Otherwise .TRUE.
 CALLS: ***
	ArrI4Zero, ArrR8Copy, ArrR8Zero, jpl_init, jpl_message, jpl_split, jpl_state
 CALLED BY:
	Time2jpl_eph, jpl_eph
 RESTRICTIONS:
	The ephemeris files are organized in records covering periods of 32 days.
	When the ephemeris is accessed for a large number of times inside a time
	range less than 32 days, the ephemeris file is accessed only once or twice,
	reading in 32-days worth of data.

	In this case it may be advantageous to close the ephemeris file
	explicitly using jpl_close after each jpl_eph2 call. jpl_state will work
	with the data in memory until a time outside the 32-day range is requested.
	If this happens the appropriate ephemeris file is opened, and the required
	record is read. This way the ephemeris file is open only for those brief
	moments when a new 32-day period is needed. The disadvantage is a speed
	penalty incurred because of repeated opening of files.

	NOTE: currently the ephemeris file is closed after a record is read,
	so a call to jpl_close is not needed. To keep the ephemeris file open
	the call to iFreeLun in jpl_state needs to be commented out.
 PROCEDURE:
	Currently two ephemeris files are accessed: 1950-2000 and 2000-2050.
 MODIFICATION HISTORY:
	????, Paul Hick (UCSD/CASS)
		Based on original JPL package. See:
		ftp://ssd.jpl.nasa.gov/pub/eph/planets/fortran/
	FEB-2005, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
		Allow 0 to represent Sun (in addition to 11)


jpl_init $SMEI/ucsd/gen/for/lib/ephem/jpl_state.f
[Previous] [Next]
 NAME:
	jpl_init
 PURPOSE:
	Initializes the JPL planetary ephemeris and opens an ephemeris file
	(internal use by jpl_eph2 only)
 CALLING SEQUENCE:
	entry jpl_init(et,bOK)
 INPUTS:
	et(2)	double precision	ephemeris time
 OUTPUTS:
	bOK	logical			.TRUE.: ephemeris data available
						(it is OK to call jpl_state)
					.FALSE.: no ephemeris available.
						(do not bother to call jpl_state)
 CALLED BY:
	jpl_eph2
 SIDE EFFECTS:
	The variable NR (record for time et) is set here and will be used by jpl_state.
	The ephemeris file DOES NOT need to be open. As long as the record
	still in memory matches NR, jpl_state has all the information it needs.
 CALLS: ***
	CvI4, CvR8, Say, bOSFindClose, bOpenFile, iFilePath, iFreeLun, iSearch, jpl_inside
	jpl_interp
 SEE ALSO:
	jpl_interp, jpl_split, jpl_state
 PROCEDURE:
	Entry point in jpl_state
	The ephemeris files are located in $EPHEM/jpl

	iRecl = 1*2*NCOEFFS	! Multiplier for recordlength in open statement
	if (cOpSys .ne. OS__VMS) iRecl = 4*2*NCOEFFS
	open (iU, file=cFile, access='DIRECT', form='UNFORMATTED', recl=iRecl, status='OLD')
 MODIFICATION HISTORY:
	???-????, Paul Hick (UCSD/CASS)
	FEB-2005, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
		Substantial rewrite.


jpl_inside $SMEI/ucsd/gen/for/lib/ephem/jpl_inside.f
[Previous] [Next]
 NAME:
	jpl_inside
 PURPOSE:
	Check whether specified time is in ephemeris file
 CALLING SEQUENCE:
	function jpl_inside(et,SS)
 CALLS:
	jpl_split
 CALLED BY:
	jpl_close, jpl_init, jpl_state
 PROCEDURE:
 MODIFICATION HISTORY:
	FEB-2005, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


jpl_interp $SMEI/ucsd/gen/for/lib/ephem/jpl_interp.f
[Previous] [Next]
 NAME:
	jpl_interp
 PURPOSE:
	Differentiates and interpolates a set of Chebyshev
	coefficients to give position and velocity
 CALLING SEQUENCE:
	subroutine jpl_interp(BUF,T,NCF,NCM,NA,IFL,pv)
 INPUTS:
	BUF	1ST LOCATION OF ARRAY OF D.P. CHEBYSHEV COEFFICIENTS OF POSITION
	    T   T(1) IS DP FRACTIONAL TIME IN INTERVAL COVERED BY
		COEFFICIENTS AT WHICH INTERPOLATION IS WANTED
		(0 .LE. T(1) .LE. 1).  T(2) IS DP LENGTH OF WHOLE
		INTERVAL IN INPUT TIME UNITS.
	NCF	# OF COEFFICIENTS PER COMPONENT
	NCM	# OF COMPONENTS PER SET OF COEFFICIENTS (3 or 2)
	NA	# OF SETS OF COEFFICIENTS IN FULL ARRAY
		(I.E., # OF SUB-INTERVALS IN FULL INTERVAL)
	IFL  INTEGER FLAG: =1 FOR POSITIONS ONLY
			   =2 FOR POS AND VEL
 OUTPUTS:
	pv	INTERPOLATED QUANTITIES REQUESTED.  DIMENSION
		EXPECTED IS pv(NCM,IFL), DP.
 CALLED BY:
	jpl_close, jpl_init, jpl_state
 MODIFICATION HISTORY:


jpl_message $SMEI/ucsd/gen/for/lib/ephem/jpl_message.f
[Previous] [Next]
 NAME:
	jpl_message
 CALLING SEQUENCE:
	subroutine jpl_message(cSay,et,cStr)
 INPUTS:
	cSay	character*(*)		leading string passed to Say
	et(2)	double precision	ephemeris time
	cStr	character*(*)		trailing string passed to Say
 CALLS: ***
	Say, Time2Day8, Time2JD, cTime2Str
 CALLED BY:
	jpl_eph2
 MODIFICATION HISTORY:
	FEB-2005, Paul Hick (UCSD/CASS; pphick@ucsd.edu)


jpl_split $SMEI/ucsd/gen/for/lib/ephem/jpl_split.f
[Previous] [Next]
 NAME:
	jpl_split
 PURPOSE:
	Breaks a double precision number into an integer and fractional part
 CALLING SEQUENCE:
	subroutine jpl_split(TT,FR)
 INPUTS:
       TT	double precision	input number
 OUTPUTS:
       FR(2)	double precision	output integer and fraction
					FR(1): integer part
					FR(2): fractional part (always >= 0)
 CALLED BY:
	jpl_eph2, jpl_inside
 MODIFICATION HISTORY:
	???-????, Paul Hick (UCSD/CASS; pphick@ucsd.edu)
		From original JPL package


jpl_state $SMEI/ucsd/gen/for/lib/ephem/jpl_state.f
[Previous] [Next]
 NAME:
	jpl_state
 PURPOSE:
	Reads and interpolates ephemeris
	(internal use by jpl_eph2 only)
 CATEGORY:
	gen/for/lib
 CALLING SEQUENCE:
	subroutine jpl_state(et,lst,pv,bKm,bBary,EMR,bOK)
 INPUTS:
	et(2)	double precision
		Julian ephemeris epoch at which interpolation is wanted.
		Any combination et(1)+et(2) insided the time span covered by the file
		is allowed:
		A. put entire epoch in et(1) and set et(2)=0
		B. for maximum interpolatin accuracy, set et(1) to the most recent midnight
		   before the interpolation time, and put the remaining fraction in et(2)
		C. pick a fixed epoch for et(1) and put the elapsed time since that
		   epoch in et(2)
	lst(15)	integer
		array specifying what interpolation is wanted for each of the bodies
		=0, no interpolation
		=1, position only
		=2, position and velocity
	The designation of the astronomical bodies is the same as used for arguments
	NTARG and NCENT in jpl_eph
 OUTPUTS:
	pv(6,15)	double precision
		array with the interpolated quantities
		THE BODY SPECIFIED BY lst(I) WILL HAVE ITS STATE IN THE ARRAY STARTING AT
		pv(1,I).  (ON ANY GIVEN CALL, ONLY THOSE WORDS IN 'pv' WHICH ARE AFFECTED BY
		THE FIRST 10 'lst' ENTRIES (AND BY lst(14) IF LIBRATIONS ARE ON THE FILE)
		ARE SET.  THE REST OF THE 'pv' ARRAY IS UNTOUCHED.)  THE ORDER OF COMPONENTS
		STARTING IN pv(1,I) IS: X,Y,Z,DX,DY,DZ.

		ALL OUTPUT VECTORS ARE REFERENCED TO THE EARTH MEAN EQUATOR AND EQUINOX OF J2000
		IF THE DE NUMBER IS 200 OR GREATER; OF B1950 IF THE DE NUMBER IS LESS THAN 200.

		The  Moon state is always geocentric. THE OTHER NINE STATES ARE EITHER HELIOCENTRIC
		OR SOLAR-SYSTEM BARYCENTRIC, DEPENDING ON THE SETTING OF bBary

	pv(6,11)ARRAY CONTAINING THE BARYCENTRIC POSITION AND VELOCITY OF THE SUN.
	pv(6,12)NUTATIONS, IF ON FILE, ARE PUT INTO pv(K,12) IF lst(12) IS 1 OR 2.
		THE ORDER OF QUANTITIES IN pv IS:
 			D PSI  (NUTATION IN LONGITUDE)
			D EPSILON (NUTATION IN OBLIQUITY)
			D PSI DOT
			D EPSILON DOT
	pv(6,13)LUNAR LIBRATIONS, IF ON FILE, ARE PUT INTO pv(K,13) IF lst(13) IS 1 OR 2.
 CALLS: ***
	CvI4, CvR8, Say, bOSFindClose, bOpenFile, iFilePath, iFreeLun, iSearch, jpl_inside
	jpl_interp
 CALLED BY:
	jpl_eph2
 SEE ALSO:
	jpl_eph, jpl_init
 INCLUDE:
		include		'dirspec.h', 	include		'filparts.h', 	include		'openfile.h', O-Z)
	implicit double precision (A-H
 PROCEDURE:
 MODIFICATION HISTORY:


jpl_test $SMEI/ucsd/gen/for/main/jpl_test.f
[Previous] [Next]
 NAME:
	jpl_test
 PURPOSE:
	Test program for JPL ephemeris
 CATEGORY:
	Ephemeris
 CALLING SEQUENCE:
	program jpl_test
 INPUTS:
	(file $sys/jpl/testpo.405)
 OUTPUTS:
	(none)
 INCLUDE:
	include		'dirspec.h'
 CALLS: ***
	iFilePath, iGetLun, jpl_eph
 PROCEDURE:
	Compares data read from the ephemeris files with
	data in the testpo.405 file.
 MODIFICATION HISTORY:
	JAN-2001, Paul Hick (UCSD; pphick@ucsd.edu)


Julian $SMEI/ucsd/gen/for/lib/gen/julian.f
[Previous] [Next]
 NAME:
	Julian
 PURPOSE:
	Of the four quantities, date, Julian day number, Julian and Besselian
	epoch, one is supplied. The other three are then calculated.
 CATEGORY:
	Time keeping
 CALLING SEQUENCE:
	subroutine Julian(IDIN,iYr,Doy,JDio,JEpoch)
 INPUTS:
	IDIN	integer		ID=0  date    --> JD, Julian epoch, Besselian epoch
				=1  JD      --> Date, Julian epoch, Besselian epoch
				=2  Julian epoch    --> Date, JD, Besselian epoch
		(not active)	=3  Besselian epoch --> Date, JD, Julian epoch
				Add 10: use modified Julian days (=JD-2400000.5)
				Add 20: use days relative to Jan. 1, 2000 (=JD-2451544.5)
  INPUTS/OUTPUTS: (depending on value of ID)
	iYr	integer			year; the year xxxBC should be entered as -xxx+1.
	Doy	real			day of year (including fraction for the time of day).
	JD	double precision	Julian day
	JEpoch	double precision	Julian epoch = time in Julian years
 CALLED BY:
	AdjustJDCar, BList_NSO_NOAA, BList_WSO_NOAA, ECLIPTIC_EQUATOR
	ECLIPTIC_HELIOGRAPHIC, ExtractInsitu, GIPSCAST, GIPSIMP, HERDISK, HOSOrbit, JD_SYNC
	MAP_CarrTime, MAP_TZERO, MKVTRACE, MessengerOrbit, N_CARRINGTON, Pandora
	PlanetOrbit, READ_HOS, ReadG, ReadGHD, ReadVIPS, ReadVIPSLOSCheck, ReadVIPSLOSCheckn
	ReadVIPSn, SetGrid, StereoAOrbit, StereoBOrbit, StereoOrbit, SunNewcomb
	UlyssesOrbit, Write3D_bb_UT, Write3D_nv_UT, XMAP_SC_POS, ipsd, ipsdt, sim_MOD
 PROCEDURE:
	Dates before 5 october 1582 are interpreted as Julian dates;
	after 15 october as Gregorian dates.
	5 october 1582 (Julian) = 15 october 1582 (Gregorian).

	RJD	'relative' Julian day = (Julian day - 2451544.5)      
	J2000.0 = 2000 January 1.5d TDB = JD 2451545.0
	JD 2451544.5 = 2000 January 1.0d (i.e. 1 January, midnight)
	Check:	JD 2398220.0 =  1854 Jan.  1.5d
		JD 2299161.0 =  1582 Oct. 15.5d (Gregorian calender)
			     =  1582 Oct.  5.5d (Julian calender)
				(Doy = 278.5)
		JD       0.0 = -4712 Jan.  1.5d

	JEpoch 1900 = JD 2415020.0 = Jan 0.5 1900
	JEpoch 2000 = JD 2451545.0 = Jan 1.5 2000
 MODIFICATION HISTORY:
	1989-1990, Paul Hick (MPAE,UCSD/CASS; pphick@ucsd.edu)


Julian8 $SMEI/for/tdlib/julian8.f
[Previous] [Next]
 NAME:
	Julian8
 PURPOSE:
	Of the four quantities, date, Julian day number, Julian and Besselian
	epoch, one is supplied. The other three are then calculated.
 CATEGORY:
	Time keeping
 CALLING SEQUENCE:
	subroutine Julian8(IDIN,iYr,Doy8,JDio,JEpoch)
 INPUTS:
	IDIN	integer		ID=0  date    --> JD, Julian epoch, Besselian epoch
				=1  JD      --> Date, Julian epoch, Besselian epoch
				=2  Julian epoch    --> Date, JD, Besselian epoch
		(not active)	=3  Besselian epoch --> Date, JD, Julian epoch
				Add 10: use modified Julian days (=JD-2400000.5)
				Add 20: use days relative to Jan. 1, 2000 (=JD-2451544.5)
  INPUTS/OUTPUTS: (depending on value of ID)
	iYr	integer			year; the year xxxBC should be entered as -xxx+1.
	Doy8	double precision	day of year (including fraction for the time of day).
	JD	double precision	Julian day
	JEpoch	double precision	Julian epoch = time in Julian years
 CALLED BY:
	ECLIPTIC_HELIOGRAPHIC8, Extractd, Extractd3d, MkTimes, SunNewcomb8, XMAP_SC_POS8
 PROCEDURE:
	Dates before 5 october 1582 are interpreted as Julian dates;
	after 15 october as Gregorian dates.
	5 october 1582 (Julian) = 15 october 1582 (Gregorian).

	RJD	'relative' Julian day = (Julian day - 2451544.5)      
	J2000.0 = 2000 January 1.5d TDB = JD 2451545.0
	JD 2451544.5 = 2000 January 1.0d (i.e. 1 January, midnight)
	Check:	JD 2398220.0 =  1854 Jan.  1.5d
		JD 2299161.0 =  1582 Oct. 15.5d (Gregorian calender)
			     =  1582 Oct.  5.5d (Julian calender)
				(Doy8 = 278.5)
		JD       0.0 = -4712 Jan.  1.5d

	JEpoch 1900 = JD 2415020.0 = Jan 0.5 1900
	JEpoch 2000 = JD 2451545.0 = Jan 1.5 2000
 MODIFICATION HISTORY:
	1989-1990, Paul Hick (MPAE,UCSD/CASS; pphick@ucsd.edu)