MPFS reduction routines HELP

Last modified: Sat Aug 21 09:32:58 1999.


List of Routines


Routine Descriptions

ADD_HEADER

[Next Routine] [List of Routines]
 NAME:
	ADD_HEADER
 PURPOSE:
	addition information from FITS-headers MPFS-frames
 DESCRIPTION: 
	The function computes the total exposure, mean value zenit distance
	and modified FITS header
 CALLING SEQUENCE:
	Result =ADD_HEADER( headers )
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	Headers = String array FITS-headers from the MPFS data

 OUTPUTS:
	Header = String array containing the header from the FITS file.
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	
	Procedures:  SXADDPAR,SXADDHIST

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\add_head.pro)


CHECK_FITS

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	CHECK_FITS
 PURPOSE:
	Given a FITS array IM, and a associated FITS or STSDAS header HDR, this
	procedure will check that
		(1) HDR is a string array, and IM is defined and numeric   
		(2) The NAXISi values in HDR are appropiate to the dimensions 
                   of IM
		(3) The BITPIX value in HDR is appropiate to the datatype of IM
	If HDR contains a DATATYPE keyword (as in STSDAS files), then this is 
	also checked against the datatype of of IM
	If the UPDATE keyword is present, then FITS header will be modified, if
	necessary, to force agreement with the image array

 CALLING SEQUENCE:
	check_FITS, im, hdr, [ dimen, idltype, /UPDATE, /NOTYPE, /SDAS ]

 INPUTS:
	IM -  FITS or  STSDAS array, (e.g. as read by SXREAD or READFITS )
	HDR - FITS or  STSDAS header (string array) associated with IM

 OPTIONAL OUTPUTS:
	dimen - vector containing actual array dimensions
	idltype- data type of the FITS array as specified in the IDL SIZE
		function (1 for BYTE, 2 for INTEGER*2, 3 for INTEGER*4, etc.)

 OPTIONAL KEYWORD INPUTS:
	/NOTYPE - If this keyword is set, then only agreement of the array
		dimensions with the FITS header are checked, and not the 
		data type.
	/UPDATE - If this keyword is set then the BITPIX, NAXIS and DATATYPE
		FITS keywords will be updated to agree with the array
	/SDAS - If this keyword is set then the header is assumed to be from
		an SDAS (.hhh) file.    CHECK_FITS will then ensure that (1)
		a DATATYPE keyword is included in the header and (2) BITPIX
		is always written with positive values.
	/FITS -  If this keyword is present then CHECK_FITS assumes that it is
		dealing with a FITS header and not an SDAS header, see notes
		below.

 SYSTEM VARIBLE:
	If there is a fatal problem with the FITS array or header then !ERR is
	set to -1.   ( If the UPDATE keyword was supplied, and the header could
	be fixed then !ERR = 0.)

 PROCEDURE:
	Program checks the NAXIS1 and NAXIS2 parameters in the header to
	see if they match the image array dimensions.

 NOTES:
	An important distinction between an STSDAS header and a FITS header
	is that the BITPIX value in an STSDAS is always positive, e.g. BITPIX=32
	for REAL*4 data.    Users should use either the /SDAS or the /FITS 
	keyword if it is important whether the STSDAS or FITS convention for 
	REAL*4 data is used.     Otherwise, CHECK_FITS assumes that if a 
	DATATYPE keyword is present then it is dealing with an STSDAS header.

 MODIFICATION HISTORY:
	Written, December 1991  W. Landsman Hughes/STX to replace CHKIMHD
	No error returned if NAXIS=0 and IM is a scalar   W. Landsman  Feb 93
	Fixed bug for REAL*8 STSDAS data W. Landsman July 93
	Make sure NAXIS agrees with NAXISi  W. Landsman  October 93

(See d:\rsi\idl40\mpfs.lib\CHECK_FI.PRO)


CONV_VAX_UNIX

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   CONV_VAX_UNIX     
 PURPOSE:
    To convert VAX IDL data types to UNIX (Sun,MIPS,etc.) IDL data types.
    The architecture is obtained from IDL sys.var. !VERSION.ARCH.   
    (Derived from the IUE procedure VAX2SUN)

 CALLING SEQUENCE:
    		var_unix = conv_vax_unix( var_vax )
 PARAMETERS:
    variable (REQ) (IO) (BIFDC) (012)
        The data variable to be converted.  This may be a scalar
	 or an array.  All IDL datatypes are valid (including structures).
	The result of the conversion is returned by the function.
 KEYWORD:  
	TARGET_ARCH = name (string) of desired target architecture
			if using this function on a VAX.
		otherwise !VERSION.ARCH is used to determine the conversion.
 EXAMPLE:
	Read a 100 by 100 matrix of floating point numbers from a data
	file created on a VAX.  Then convert the matrix values into Sun format.

	IDL> openr,1,'vax_float.dat'
	IDL> data = fltarr(100,100)
	IDL> readu,1,data
	IDL> data = conv_vax_unix( data )

 MODIFICATION HISTORY:
       Written   F. Varosi               August 1990
       Modified  P. Keegstra             April 1992
           			Implemented MIPSEL architecture

(See d:\rsi\idl40\mpfs.lib\CONV_VAX.PRO)


CORRSENT

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	CORRSENT
 PURPOSE:
	correction spectral sensitivity
 DESCRIPTION:
	The function computes the absolute spectral distribution in reduced
	2-dimensional array MPFS-spectra in erg/cm^2/sec/A.
	Routine read vector spectral sensitivity
	from disk in working directory with standard name 'sent.fts',
	sky-substraction linearised spectra (filename='*-sky.fts', where
	image_type='*')	and modified FITS header

 CALLING SEQUENCE:
	CORRSENT, LOG,file_name,PLOT=plot
 CATEGORY:
	reduction MPFS-data

 INPUTS:
	LOG = String scalarfile name of FITS-header from the LOG observation MPFS data
	image_type= string scalar ( value 'obj' or 'test'

 OUTPUTS:
	Saved in working directory in file '*_abs.fts'

 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	PLOT - if present  then plotted spectra central part lens array to display,
	else save plot to POSTSCRIPT file in working directory with name '*.ps'

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function :   DEF_WDIR,READ_FTS,SXPAR,OS_FAMILY

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\corrsent.pro)


COSIN_APOD

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	COSIN_APOD

 PURPOSE:
	Apodize a 1-D data set with a cosine apodizing function.

 CALLING SEQUENCE:
	Result = COSIN_APOD(N,P)

 INPUTS:
	N = number of points of the data set.

 OPTIONAL INPUTS:
	P = dimension of the cosine function, in percentage of N.
		Default is 10 %.

 OUTPUT:
	Result = a cosine window function.

 KEYWORDS:
	None.

 COMMON BLOCKS:
	None.

 SIDE EFFECTS:
	None.

 RESTRICTIONS:
	None.

 PROCEDURE:
	The two edges of the output array are multiplied by a cosine
	function.

 MODIFICATION HISTORY:
	Written by Roberto Luis Molowny Horas, January 1994.

(See d:\rsi\idl40\mpfs.lib\cosin_ap.pro)


COSMETIC

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	COSMETIC
 PURPOSE:
	replace  bad column in CCD-frame
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=COSMETIC(image_in,bad_column)
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	image_in = 2-dimensional float array  CCD-frame MPFS-data
	bad_column = 1-dimensional integer array value bad column

 OUTPUTS:
	Result = 2-dimensional float array 
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	no

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\cosmetic.pro)


CREA_DISPER

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	CREA_DISPER
 PURPOSE:
      Identefication comparison spectra & creation array coefficient dispersion curve
 DESCRIPTION: 
	The routine compare position lines in  2D-array comparison MPFS-spectrum 
	(from file 'neon_s.fts') with tabulated wavelength from file 'LINES.TAB',
	 and create after 2-dimensional
	 polynomial approximation array dispersion coefficients
	
 CALLING SEQUENCE:
	CREA_DISPER,LOGFILE,FWHM,N_deg,PLOT=plot

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOG = String scalar of file name  FITS-header from the LOG observation
	FWHM = width spectral lines in px
	N_deg = degree of 2D-polynomial approximation dispersion curve

 OUTPUTS:
	 2-dimensional ( N_deg+1) x N_spectra float array coefficient dispersion curve,
        saved to the disk in  working directory with  standard name 'disper.fts' and
	 print in file 'disper.txt'. 
	 Last value in every string is rms approximation i px			
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	PLOT - if present 2-d errors of approximation plotted to display,
	else save plot to POSTSCRIPT file in working directory with name 'err_line.ps'	

 RESTRICTIONS:
	no
 NOTES:
	no

 PROCEDURES USED:
	Function :   DEF_WDIR,DEF_RDIR,DEF_NAME,READ_FTS,INP_WAVE
	Procedures:  CRSPROD,GOODPOLY

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\crea_dis.pro)


CREA_TRA

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	CREA_TRA
 PURPOSE:
	creation traectory for every spectra
 DESCRIPTION: 
	Routine interpolated traectory etalon spectra from file 'eta_tra.fts'
	in working directory in position every fiber. Routine used table
	position etalon fiber from file 'ETALON.POS' and spectra fiber
	 (file 'FIBER.POS'). Result save in file 'fib_tra.fts'
	
 CALLING SEQUENCE:
	CREA_TRA, LOGFILE
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)

 OUTPUTS:
	saved in file 'fib_tra.fts'
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function :	DEF_WDIR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\crea_tra.pro)


CROSS_NORM

[Previous Routine] [Next Routine] [List of Routines]
NAME: 
      CROSS_NORM
 
CLASS: 

    cross-correlation 
 
CATEGORY: 
 
PURPOSE: 
 
   To compute a cross correlation for two spectral segments 
   which are sampled on the same linear or log(lambda) scale,normalised at 
   dispersion
 
CALLING SEQUENCE: 
 
   result=CROSS_NORM(FFIR,FSEC,NSPR) 
 
PARAMETERS: 
 
   FFIR    (REQ) (I)  (1) (F) 
           Required input vector giving the flux data for the first  
           spectrum. 
 
   FSEC    (REQ) (I)  (1) (F)  
           Required input vector giving the flux data for the second   
           spectrum.  
  
   NSPR    (REQ) (I)  (0) (F)  
           Required input parameter specifying the spectral range to  
           be considered in the cross-correlation function.  
  
  
EXAMPLES:  
  
    To compute the cross-correlation function for two spectra, FIRST  
    and SECOND, using the recommended initial spectral range from CRSCOR,  
  
    result=CROSS_NORM(FIRST,SECOND)
  
SYSTEM VARIABLES USED:  
  
INTERACTIVE INPUT:  
  
SUBROUTINES CALLED:  
  
    PARCHECK  
  
FILES USED:  
  
SIDE EFFECTS:  
  
RESTRICTIONS:  
  
NOTES:  
       Assumes same number of elements in both spectra. (Both fluxes are  
       divided by the number of elements in the first spectrum.)  
  
PROCEDURE:  
  
     CROSS is determined for (2*nspr + 1) tags or shifts going from -15  
     to +15 shifts from the starting locations.   
     After subtracting the average flux from each spectrum, the cross  
     correlation function is computed as follows for each point in   
     the spectra,   
      TEMP = (second spectrum) * SHIFT(first spectrum,ns)  
      CROSS(L) = TOTAL(TEMP(ls:us)/nele)   
  
  
MODIFICATION HISTORY:  
  
	25 Jun 1991  PJL cleaned up; added PARCHECK and parameter eq 0  
			 print; tested on SUN and VAX; updated prolog  
  

(See d:\rsi\idl40\mpfs.lib\CROSS_N.PRO)


CRSPROD

[Previous Routine] [Next Routine] [List of Routines]
NAME: 
      CRSPROD 
 
CLASS: 

    cross-correlation 
 
CATEGORY: 
 
PURPOSE: 
 
   To compute a normalized cross correlation for two spectral segments 
   which are sampled on the same linear or log(lambda) scale.  
 
CALLING SEQUENCE: 
 
   CRSPROD,FFIR,FSEC,NSPR,CROSS,CRMIN,CRMAX 
 
PARAMETERS: 
 
   FFIR    (REQ) (I)  (1) (F) 
           Required input vector giving the flux data for the first  
           spectrum. 
 
   FSEC    (REQ) (I)  (1) (F)  
           Required input vector giving the flux data for the second   
           spectrum.  
  
   NSPR    (REQ) (I)  (0) (F)  
           Required input parameter specifying the spectral range to  
           be considered in the cross-correlation function.  
  
   CROSS   (REQ) (O)  (1) (F)  
           Required output vector containing the cross-correlation   
           function.  
  
   CRMIN   (REQ) (O)  (0) (F)  
           Required output vector containing the minimum of the   
           cross-correlation function.   
  
   CRMAX   (REQ) (O)  
           Required output vector containing the maximum of the   
           cross-correlation function.   
  
EXAMPLES:  
  
    To compute the cross-correlation function for two spectra, FIRST  
    and SECOND, using the recommended initial spectral range from CRSCOR,  
  
    CRSPROD,FIRST,SECOND,15,CROSS,CRMIN,CRMAX  
  
SYSTEM VARIABLES USED:  
  
INTERACTIVE INPUT:  
  
SUBROUTINES CALLED:  
  
    PARCHECK  
  
FILES USED:  
  
SIDE EFFECTS:  
  
RESTRICTIONS:  
  
NOTES:  
       Assumes same number of elements in both spectra. (Both fluxes are  
       divided by the number of elements in the first spectrum.)  
  
PROCEDURE:  
  
     CROSS is determined for (2*nspr + 1) tags or shifts going from -15  
     to +15 shifts from the starting locations.   
     After subtracting the average flux from each spectrum, the cross  
     correlation function is computed as follows for each point in   
     the spectra,   
      TEMP = (second spectrum) * SHIFT(first spectrum,ns)  
      CROSS(L) = TOTAL(TEMP(ls:us)/nele)   
  
  
MODIFICATION HISTORY:  
  
	25 Jun 1991  PJL cleaned up; added PARCHECK and parameter eq 0  
			 print; tested on SUN and VAX; updated prolog  
  

(See d:\rsi\idl40\mpfs.lib\crsprod.pro)


CUBE_CLE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	CUBE_CLE
 PURPOSE:
	cleaning cosmic hits in data cube
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = CUBE_CLE( image, tresh )

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	image - cube of data in 2D-view : array Nz x (Nx*Ny) elements for cleaning
	tresh - level discrimination data in sigma (typical value 10)
 OUTPUTS:
	Result - cleaned cube
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\cube_cle.pro)


DATATYPE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
       DATATYPE
 PURPOSE:
       Datatype of variable as a string (3 char or spelled out).
 CATEGORY:
 CALLING SEQUENCE:
       typ = datatype(var, [flag])
 INPUTS:
       var = variable to examine.         in
       flag = output format flag (def=0). in
 KEYWORD PARAMETERS:
       Keywords:
         /DESCRIPTOR returns a descriptor for the given variable.
           If the variable is a scalar the value is returned as
           a string.  If it is an array a description is return
           just like the HELP command gives.  Ex:
           datatype(fltarr(2,3,5),/desc) gives
             FLTARR(2,3,5)  (flag always defaults to 3 for /DESC).
 OUTPUTS:
       typ = datatype string or number.   out
          flag=0    flag=1      flag=2    flag=3
          UND       Undefined   0         UND
          BYT       Byte        1         BYT
          INT       Integer     2         INT
          LON       Long        3         LON
          FLO       Float       4         FLT
          DOU       Double      5         DBL
          COM       Complex     6         COMPLEX
          STR       String      7         STR
          STC       Structure   8         STC
          DCO       DComplex    9         DCOMPLEX
 COMMON BLOCKS:
 NOTES:
 MODIFICATION HISTORY:
       Written by R. Sterner, 24 Oct, 1985.
       RES 29 June, 1988 --- added spelled out TYPE.
       R. Sterner, 13 Dec 1990 --- Added strings and structures.
       R. Sterner, 19 Jun, 1991 --- Added format 3.
       R. Sterner, 18 Mar, 1993 --- Added /DESCRIPTOR.
       R. Sterner, 1995 Jul 24 --- Added DCOMPLEX for data type 9.
       Johns Hopkins University Applied Physics Laboratory.

 Copyright (C) 1985, Johns Hopkins University/Applied Physics Laboratory
 This software may be used, copied, or redistributed as long as it is not
 sold and this copyright notice is reproduced on each copy made.  This
 routine is provided as is without any express or implied warranties
 whatsoever.  Other limitations apply as described in the file disclaimer.txt.

(See d:\rsi\idl40\mpfs.lib\DATATYPE.PRO)


DEF_NAME

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	DEF_NAME
 PURPOSE:
	definition filename of different type exposure MPFS-data
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=DEF_NAME(FILELOG,TYPE_EXP,N_EXP)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	TYPE_EXP = string scalar type exposure (values: 'bias','obj','star','flat',
		   'eta','star','test')

 OUTPUTS:
	Result = string scalar filename for reading (without extention)
		
 OPTIONAL OUTPUT:
	N_exp - number exposures with every value TYPE_EXP

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\def_name.pro)


DEF_RDIR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	DEF_RDIR
 PURPOSE:
	DEFINIRION DIRECTORY FOR READING DATA FROM LOG FILE
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=DEF_RDIR(FILELOG)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	

 OUTPUTS:
	Result = string scalar name directory for reading 
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\def_rdir.pro)


DEF_SENT

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	DEF_SENT
 PURPOSE:
      definition  spectral sensitivity
 DESCRIPTION: 
	routine used linearised MPFS-spectra of standard star (filename in working
	directory 'star_lin.fts'), information from FITS-header about total exposure,
	gain CCD, mean value zenit distance for calculation observed flux. Observed 
	flux compare with absolute energy distribution star.
	Routine used ASCII data files for the Oke (AJ,99, 1621, 1990) optical
	spectrophotometric standard stars	
 CALLING SEQUENCE:
	DEF_SENT, LOGFILE, PLOT=plot
 CATEGORY:
	reduction MPFS-data		
 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)	
 OUTPUTS:
	 in working directory saved 1-dimensional  float array spectral sensitivity
	 in  erg/cm^2/sec/A per ADU (standard filename 'sent.fts');        				
 OPTIONAL OUTPUT:
	no
 OPTIONAL INPUT KEYWORDS:
	PLOT - if present the  curve DQE  plotted to display,
	else save plot to POSTSCRIPT file in working directory with name 'DQE.ps'	
 RESTRICTIONS:
	no
 NOTES:
	no;
 PROCEDURES USED:
	Function :   DEF_WDIR,NAME_TAB,READ_FTS,INP_WAVE,OS_FAMILY
	Procedures:  SXPAR,SXADDPAR,MKHDR
 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\def_sent.pro)


DEF_SHIFT

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	DEF_SHIFT
 PURPOSE:
	definition  shift between two image in any direction
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = DEF_SHIFT ( image1, image2, coord, c, w)
 CATEGORY:
	reduction MPFS-data		

INPUTS :
      image1 and image2 - images to be shifted
      coord - string scalar define shift direction (value 'x' or 'y')
      c - magnification for calculation cross-correlation
      w - width band integration in cross-shift direction

 OUTPUTS:
	Result = float scalar
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	CRSPROD

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\DEF_SHI.PRO)


DEF_WDIR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	DEF_WDIR
 PURPOSE:
	DEFINIRION DIRECTORY FOR WRITING DATA 
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=DEF_WDIR(FILELOG)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	

 OUTPUTS:
	Result = string scalar name directory for writing
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\def_wdir.pro)


EXTRACT

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	EXTRACT
 PURPOSE:
	extraction spectra in frame MPFS-image
 DESCRIPTION: 
	Routine extracted spectra in MFPS-frame in file with standard name '*_n.fts'
	('*'=image_type) along traectory from file with standard name 'fib_tra.fts',
	for obj-fibers, and along traectory etalon (from file 'eta_tra.fts' for sky
	Routine modified FITS-header
 CALLING SEQUENCE:
	EXTRACT, LOGFILE, fwhm, image_type

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	fwhm = width band of spectra
	image_type = string scalar type exposure (values: 'obj','star','eta',
						'neon','test')
		   

 OUTPUTS:
	Result - array float point spectra saved to disk in working directory
	with standard name '*_s.fts'.
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	DEF_WDIR,SXADDPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\extract.pro)


FDECOMP

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	FDECOMP
 PURPOSE:
	Routine to decompose a file name for any operating system

 CALLING SEQENCE:
	FDECOMP, filename, disk, dir, name, qual, version, [OSFamily = ]

 INPUT:
	filename - string file name, scalar

 OUTPUTS:
	All the output parameters are scalar strings
	disk - disk name, always '' on a Unix machine, scalar string
	dir - directory name, scalar string
	name - file name, scalar string
	qual - qualifier, set equal to the characters beyond the last "."
	version - version number, always '' on a non-VMS machine, scalar string

 OPTIONAL INPUT KEYWORD:
	OSFamily - one of the four scalar strings specifying the operating 
		system:  'vms','windows','MacOS' or 'unix'.    If not supplied,
		then OS_FAMILY() is used to determine the operating system.
 EXAMPLES:
	Consider the following file names 

	Unix:    file = '/rsi/idl40/avg.pro' 
	VMS:     file = '$1$dua5:[rsi.idl40]avg.pro;3
	Mac:     file = 'Macintosh HD:Programs:avg.pro'
	Windows: file =  'd:\rsi\idl40\avg.pro'
	
	then IDL> FDECOMP,  file, disk, dir, name, qual, version
	will return the following

		  Disk             Dir          Name        Qual     Version
	Unix:      ''            '/rsi/idl40/'  'avg'       'pro'       ''
	VMS:     '$1$dua5'       '[RSI.IDL40]'  'avg'       'pro'       '3'
	Mac:     'Macintosh HD'  ':Programs:'   'avg'       'pro'       ''
	Windows:    'd:'         \rsi\idl40\    'avg'       'pro'       ''

 NOTES:
	(1) All tokens are removed between
		1) name and qual  (i.e period is removed)
		2) qual and ver   (i.e. VMS semicolon is removed)
	(2) On VMS the filenames "MOTD" and "MOTD." are distinguished by the 
	    fact that qual = '' for the former and qual = ' ' for the latter.

 ROUTINES CALLED:
	Function GETTOK(), OS_FAMILY()
	Users with V4.0 or later can replace OS_FAMILY() with !VERSION.OS_FAMILY
 HISTORY
	version 1  D. Lindler  Oct 1986
	Include VMS DECNET machine name in disk    W. Landsman  HSTX  Feb. 94
	Converted to Mac IDL, I. Freedman HSTX March 1994
          

(See d:\rsi\idl40\mpfs.lib\FDECOMP.PRO)


FIND_ETA

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	FIND_ETA
 PURPOSE:
      Find and creation traectory spectra etalon fibers
 DESCRIPTION:
	Routine find etalon spectra in MPFS-frame from file 'eta_n.fts' and
	create after polynomial approximation traectory etalon fibers

 CALLING SEQUENCE:
	FIND_ETA, LOGFILE, GAUSS=gauss, PLOT=plot

 CATEGORY:
	reduction MPFS-data

 INPUTS:
	LOG = String scalar of file name  FITS-header from the LOG observation

 OUTPUTS:
	 Result saved to disk in working directory in files with standard names
	 'eta_tra.fts' - 2D  float array traectory fibers
	 'eta_poly.txt' - table coefficient polynomyal approximation traectory

 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	GAUSS - if present  cross-dispersion profile fitted by gauss-function
	PLOT - if present 2-d errors of approximation plotted to display,
	else save plot to POSTSCRIPT file in working directory with name 'err_line.ps'

 RESTRICTIONS:
	no
 NOTES:
	no

 PROCEDURES USED:
	Function :   DEF_WDIR,READ_FTS
	Procedures:  FI_PEAK

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\find_eta.pro)


FI_PEAK

[Previous Routine] [Next Routine] [List of Routines]
 NAME:      
        FI_PEAK     
 PURPOSE:      
        Find peaks in a lineout      
 CATEGORY:      
        reduction MPFS-data      
 CALLING SEQUENCE:      
        peak_find      
 INPUTS:      
        xpl:    x array      
        ypl:    y array      
        pkcut:  cutoff value for determining peak      
 KEYWORD PARAMETERS:      
        no 
 OUTPUTS:      
        ipix:   pixel location of peaks, array      
        xpk:    x location of peaks, array      
        ypk:    y location of peaks, array      
        bkpk:   background at peak locations, array      
 COMMON BLOCKS:      
        None      
 SIDE EFFECTS:      
        None.      
 RESTRICTIONS:      
        None.      
 PROCEDURE:      
        no      
 MODIFICATION HISTORY: 
	Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999     

(See d:\rsi\idl40\mpfs.lib\fi_peak.pro)


FLAT_REDUCTION

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	FLAT_REDUCTION
 PURPOSE:
	reduction MPFS-image at flat field
 DESCRIPTION: 
	Routine read in working directory flat-field frame from file 'flat_i.fts'
	In flat-field frame extracted scattering ligth, end frame normalised
	Image with type '*' read from file '*_i.fts', and divided after
	scattering ligth by flat. Routine use for calculation scattering ligth
	file 'eta_tra.fts'
	
 CALLING SEQUENCE:
	FLAT_REDUCTION, LOGFILE, image_type
	
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	image_type = string scalar type exposure (values: 'obj','star','flat',
		   'eta','star','test');	

 OUTPUTS:
	Result saved to disk i working directory in file '*_n.fts'
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function  DEF_WDIR,READ_FTS, SCATTER
	Procedure SXADDPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\flat_red.pro)


GETTOK

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	GETTOK                                    
 PURPOSE:
	Function to retrieve the first part of the string
	until the character char is encountered.

 CALLING SEQUENCE:
	token = gettok( st, char )

 INPUT:
	char - character separating tokens, scalar string

 INPUT-OUTPUT:
	st - (scalar) string to get token from (on output token is removed)

 OUTPUT:
	token - scalar string value is returned 

 EXAMPLE:
	If ST is 'abc=999' then gettok(ST,'=') would return
	'abc' and ST would be left as '999' 

 HISTORY
	version 1  by D. Lindler APR,86
	Remove leading blanks    W. Landsman (from JKF)    Aug. 1991

(See d:\rsi\idl40\mpfs.lib\GETTOK.PRO)


GET_DATE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	GET_DATE
 PURPOSE:
	Return the current date in DD/MM/YY format.  This is the format
	required by the DATE and DATE-OBS keywords in a FITS header

 CALLING SEQUENCE:
	GET_DATE, dte
 INPUTS:
	None
 OUTPUTS:
	dte = An eight character scalar string specifying the current day 
		(0-31), current month (1-12), and last two digits of the 
		current year
 EXAMPLE:
	Add the current date to the DATE keyword in a FITS header,h
     
	IDL> GET_DATE,dte
	IDL> sxaddpar, h, 'DATE', dte

 REVISION HISTORY:
	Written      W. Landsman          March 1991

(See d:\rsi\idl40\mpfs.lib\GET_DATE.PRO)


GOODPOLY

[Previous Routine] [Next Routine] [List of Routines]
 NAME: 
	goodpoly 
 PURPOSE: (one line) 
	Robust fitting of a polynomial to data. 
 DESCRIPTION: 
	This is a multi-pass fitting routine that fits a fixed order polynomial 
	to the input data.  After each pass, the scatter of the fit relative 
	to the fitted line is computed.  Each point is examined to see if it 
	falls beyond THRESH sigma from the line.  If is does, it is removed 
	from the data and the fit is tried again.  This will make two attempts 
	to remove bad data. 
 CATEGORY: 
 CALLING SEQUENCE: 
	coeff = goodpoly(x,y,order,thresh,yfit,newx,newy) 
 INPUTS: 
	x      - Input dataset, independant values. 
	y      - Input dataset, dependant values. 
	order  - Order of the polynomial fit (linear = 1). 
	thresh - Sigma threshold for removing outliers. 
 OPTIONAL INPUT PARAMETERS: 
 KEYWORD PARAMETERS: 
 OUTPUTS: 
	yfit   - Fitted values for y that match the input vector. 
	newx   - X values from input that were considered good. 
	newy   - Y values from input that were considered good. 
	Return value is the set of polynomial coefficients. 
 COMMON BLOCKS: 
 SIDE EFFECTS: 
 RESTRICTIONS: 
 PROCEDURE: 
 MODIFICATION HISTORY: 
	Written 1991 Feb., Marc W. Buie, Lowell Observatory 
  93/11/12, MWB, Program fixed to return a computed y for all input x. 

(See d:\rsi\idl40\mpfs.lib\goodpoly.pro)


HOST_TO_IEEE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	HOST_TO_IEEE
 PURPOSE:
	To translate an IDL variable from the host machine representation 
	into IEEE-754 representation (as used, for example, in FITS data ).

 CALLING SEQUENCE:
	HOST_TO_IEEE, data, [ IDLTYPE = , ]

 INPUT-OUTPUT PARAMETERS:
	data - any IDL variable, scalar or vector.   It will be modified by
		HOST_TO_IEEE to convert from host to IEEE representation.  Byte 
		and string variables are returned by HOST_TO_IEEE unchanged

 OPTIONAL KEYWORD INPUTS:
	IDLTYPE - scalar integer (1-7) specifying the IDL datatype according
		to the code given by the SIZE function.      This keyword
		will usually be used when suppying a byte array that needs
		to be interpreted as another data type (e.g. FLOAT).

 EXAMPLE:
	Suppose FITARR is a 2880 element byte array to be converted to a FITS
	record and interpreted a FLOAT data.

	IDL> host_to_ieee, FITARR, IDLTYPE = 4

 METHOD:
	The BYTEORDER procedure is called with the appropriate keywords

 RESTRICTION:
	Assumes the IDL version is since 2.2.2 when the /XDRTOF keyword 
	became available to BYTEORDER.    There were two bad implementations
	in BYTEORDER for double precision: (1) in IDL V3.* for DecStations
	(!VERSION.ARCH = 'mipsel') and (2) on Dec Alpha OSF machines.
	IEEE_TO_HOST works around these cases by swapping the byte order
	directly.

 MODIFICATION HISTORY:
	Adapted from CONV_UNIX_VAX, W. Landsman   Hughes/STX    January, 1992
	Fixed Case statement for Float and Double      September, 1992
	Workaround for /DTOXDR on DecStations          January, 1993
	Workaround for /DTOXDR on Alpha OSF            July 1994
	Assume since Version 2.2.2, Ultrix problems persist   November 1994
	Add support for double complex        July, 1995
	Workaround for VAX VMS bug in BYTEORDER,/FTOXDR in V4.0   August 1995
	Workaround for VMS bug in BYTEORDER,/FTOXDR and /DTOXDR in
		V4.0.1 (sigh...)  W. Landsman   August 1995
	Workaround for /FTOXDR bug in OSF V4.0.1 September 1995

(See d:\rsi\idl40\mpfs.lib\HOST_TO_.PRO)


IEEE_TO_HOST

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	IEEE_TO_HOST
 PURPOSE:
	To translate an IDL variable in IEEE-754 representation (as used, for
	example, in FITS data ), into the host machine architecture.

 CALLING SEQUENCE:
	IEEE_TO_HOST, data, [ IDLTYPE = , ]

 INPUT-OUTPUT PARAMETERS:
	data - any IDL variable, scalar or vector.   It will be modified by
		IEEE_TO_HOST to convert from IEEE to host representation.  Byte 
		and string variables are returned by IEEE_TO_HOST unchanged

 OPTIONAL KEYWORD INPUTS:
	IDLTYPE - scalar integer (1-7) specifying the IDL datatype according
		to the code given by the SIZE function.     This keyword
		is usually when DATA is a byte array to be interpreted as
		another datatype (e.g. FLOAT).

 EXAMPLE:
	A 2880 byte array (named FITARR) from a FITS record is to be 
	interpreted as floating and converted to the host representaton:

	IDL> IEEE_TO_HOST, fitarr, IDLTYPE = 4     

 METHOD:
	The BYTEORDER procedure is called with the appropriate keyword

 RESTRICTION:
	Assumes the IDL version is since 2.2.2 when the /XDRTOF keyword 
	became available to BYTEORDER.    There were two bad implementations
	in BYTEORDER for double precision: (1) in IDL V3.* for DecStations
	(!VERSION.ARCH = 'mipsel') and (2) on Dec Alpha OSF machines.
	IEEE_TO_HOST works around these cases by swapping bytes directly

 MODIFICATION HISTORY:
	Written, W. Landsman   Hughes/STX   May, 1992
	Fixed error Case statement for float and double   September 1992
	Workaround to /XDRTOD problem on DecStations January 1993 
	Assume since Version 2.2, correct double precision problems in 
	Alpha/OSF, implement Ultrix corrections from Tom McGlynn November 1994
	Added support for double precision complex   July 1995
	Workaround for BYTEORDER, /FTOXDR bug in VAX VMS V4.0  August 1995 

(See d:\rsi\idl40\mpfs.lib\IEEE_TO_.PRO)


INP_WAVE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	INP_WAVE
 PURPOSE:
	DEFINIRION CENTRAL WAVELENGTH AND DISPERSION FROM LOG FILE
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = INP_WAVE ( FILELOG )

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	
 OUTPUTS:
	Result = 2 element vector, were first element - central wavelength in A
		second - dprevius value dispersion in A/px
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\inp_wave.pro)


IS_IEEE_BIG

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	IS_IEEE_BIG
 PURPOSE:
	Determine if the current machine is use IEEE, big-endian numbers.
       (This implies that byteorder conversions are no-ops).
 CALLING SEQUENCE:
	flag = is_ieee_big()
 INPUT PARAMETERS:
       None
 RETURNS:
       1 if the machine appears to be IEEE-compliant, 0 if not.
 COMMON BLOCKS:
	None.
 SIDE EFFECTS:
	None
 RESTRICTIONS:
 PROCEDURE:
       A sample int, long, float and double are converted using
       byteorder and compared with the original.  If there is no
       change, the machine is assumed to be IEEE compliant and
       big-endian.
 MODIFICATION HISTORY:
       Written 15-April-1996 by T. McGlynn for use in MRDFITS.

(See d:\rsi\idl40\mpfs.lib\IS_IEEE_.PRO)


LINEAR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	LINEAR
 PURPOSE:
	linearisation spectra
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = LINEAR ( spectr, disper_par, N_lin, lambda_0, d_lambda)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	spectr = 2D array MPFS extracted spectra
	disper_par = 2D array polynomial coefficits dispersion curve for every fiber
	N_lin = numper ponts in linearised spectra
	lambda_0 = beginning wavelength in A linearised spectra
	d_lambda = dispersion in A/px linearised spectra

 OUTPUTS:
	Result = 2D array spectra
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	no

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\linear.pro)


LINERISATION

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	LINERISATION
 PURPOSE:
	linearisation spectra
 DESCRIPTION: 
	Routine read extracted MPFS-spectra with type '*' from file '*_s.fts'
	in working directory and lineriarised. If parameter 'OUT_WAVE' in LOG
	observation is non-zero, routine use parameters linearisation from LOG,
	else use mean parameter linearisation (beginning wavelength and dispersion)
	calculated by file 'disper_par.fts'. Routine modified FITS-header of result
	
 CALLING SEQUENCE:
	LINERISATION, logfile, image_name
	
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	image_type = string scalar type exposure (values: 'obj','star','neon',,'test')
		  	

 OUTPUTS:
	Result saved to disk i working directory in file '*_lin.fts'
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function  DEF_WDIR,READ_FTS, OUT_WAVE
	Procedure SXADDPAR,SXADDHIST

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\lineris.pro)


MKHDR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	MKHDR
 PURPOSE:
	Make a minimal primary FITS image header or a minimal FITS IMAGE
	extension header.   If an array is supplied  then the 
	created FITS header will be appropiate to the supplied array.  
 	Otherwise, the user can specify the dimensions and datatype.

 CALLING SEQUENCE:
	MKHDR, header			;Prompt for image size and type
		or
	MKHDR, header, im, [ /IMAGE, /EXTEND ]
		or
	MKHDR, header, type, naxisx, [/IMAGE, /EXTEND ]    	

 OPTIONAL INPUTS:
	IM - If IM is a vector or array then the header will be made
		appropiate to the size and type of IM.  IM does not have
		to be the actual data; it can be a dummy array of the same
		type and size as the data.    Set IM = '' to create a dummy
		header with NAXIS = 0. 
	TYPE - If more than 2 parameters are supplied, then the second parameter
		is intepreted as an integer giving the IDL datatype e.g. 
		1 - LOGICAL*1, 2 - INTEGER*2, 4 - REAL*4, 3 - INTEGER*4
	NAXISX - Vector giving the size of each dimension (NAXIS1, NAXIS2, 
		etc.).  

 OUTPUT:
	HDR - image header, (string array) with required keywords
		BITPIX, NAXIS, NAXIS1, ... Further keywords can be added
		to the header with SXADDPAR. 

 OPTIONAL INPUT KEYWORDS:
	IMAGE   = If set, then a minimal header for a FITS IMAGE extension
		is created.    An IMAGE extension header is identical to
		a primary FITS header except the first keyword is 
		'XTENSION' = 'IMAGE' instead of 'SIMPLE  ' = 'T'
	EXTEND	= If set, then the keyword EXTEND is inserted into the file,
		with the value of "T" (true).

 RESTRICTIONS:
	(1)  MKHDR should not be used to make an STSDAS header or a FITS
		ASCII or Binary Table header.   Instead use

		SXHMAKE - to create a minimal STSDAS header
		FXHMAKE - to create a minimal FITS binary table header
		FTCREATE - to create a minimal FITS ASCII table header

	(2)  Any data already in the header before calling MKHDR
		will be destroyed.
 EXAMPLE:
	Create a minimal FITS header, HDR, for a 30 x 40 x 50 INTEGER*2 array

	      IDL> MKHDR, HDR, 2, [30,40,50]

	Alternatively, if the array already exists as an IDL variable, ARRAY,

	       IDL> MKHDR, HDR, ARRAY

 PROCEDURES CALLED:
	SXADDPAR, GET_DATE

 REVISION HISTORY:
    Written November, 1988               W. Landsman
    May, 1990, Adapted for IDL Version 2.0, J. Isensee

(See d:\rsi\idl40\mpfs.lib\MKHDR.PRO)


MOMENT

[Previous Routine] [Next Routine] [List of Routines]
 NAME:  
	moment  
 PURPOSE: (one line)  
	Compute various statistical moments of the data.  
 DESCRIPTION:  
	This routine computes the average, average deviation, standard  
	deviation, variance, skew and kurtosis of the input data.  The various  
	output quantities are always returned as floating point scalars.  
	The statistics are compute with no regard for the dimensionality of  
	the input data.  
 CATEGORY:  
	statistics  
 CALLING SEQUENCE:  
	moment_r,data,avg,avgdev,stddev,var,skew,kurt  
 INPUTS:  
	data - Input data to be analyzed.  
 OPTIONAL INPUT PARAMETERS:  
	None.  
 KEYWORD PARAMETERS:  
	None.  
 OUTPUTS:  
	avg    - Sample mean.  
	avgdev - Average deviation of the data from the mean.  
	stddev - Standard deviation of the data from the mean.  
	var    - Variance of the data from the mean.  
	skew   - Skewness, third statistical moment.  
	kurt   - Kurtosis, fourth statistical moment.  
 COMMON BLOCKS:  
	None.  
 SIDE EFFECTS:  
	None.  
 RESTRICTIONS:  
	None.  
 PROCEDURE:  
	Standard techniques, see section 13.1 in Numerical Recipies.  
 MODIFICATION HISTORY:  
	Written by Marc W. Buie, Lowell Observatory, 1992 Jan 20  

(See d:\rsi\idl40\mpfs.lib\moment_r.pro)


NAME_TAB

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	NAME_TAB
 PURPOSE:
	DEFINIRION NAME OF TABLE WITH  ABSOLUTE ENERGY DISTRIBUTION OF STAR
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=NAME_TAB(FILELOG)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	

 OUTPUTS:
	Result = string scalar name file
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\name_tab.pro)


OS_FAMILY

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	OS_FAMILY
 PURPOSE:
	Return the current operating system as in !VERSION.OS_FAMILY 

 CALLING SEQUENCE
	result = OS_FAMILY()
 INPUTS: 
	None
 OUTPUTS:
	result - scalar string containing one of the four values
		'Windows','MacOS','vms' or 'unix'
 NOTES:
	OS_FAMILY is assumed to be 'unix' if !VERSION.OS is not 'windows',
		'MacOS' or 'vms'

	To make procedures from IDL V4.0 and later compatibile with earlier
	versions of IDL, replace calls to !VERSION.OS_FAMILY with OS_FAMILY().	

 PROCEDURES CALLED
	function tag_exists
 REVISION HISTORY:
	Written,  W. Landsman     

(See d:\rsi\idl40\mpfs.lib\OS_FAMIL.PRO)


OUT_WAVE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	 OUT_WAVE
 PURPOSE:
	read parameter of linerisation from LOG observation
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result=OUT_WAVE(FILELOG)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	

 OUTPUTS:
	Result = 2 elements float point array  contain beginning wavelength in A,
		dispersion in A/px and number elements in linearised spectra
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\out_wave.pro)


PAR_LINE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	PAR_LINE
 PURPOSE:
	calculation  parameter of  line in nigth sky spectrum
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = PAR_LINE ( vector,param,FWHM,line)
 CATEGORY:
	reduction MPFS-data		

INPUTS :
	vector		input vector spectra
	param=[lambda_0,d_lambda] beginnig wavelength(A) end dispersion(A/px)
	FWHM	    	previus value width lines in px
	line		wavelength line in A
 OUTPUTS:
	Result =[flux,position(in px),FWHM(in px)] 
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	ROBOMEAN

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\par_line.pro)


READFILE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	READFILE
 PURPOSE:
	read files with MPFS-images. Will also read zip compressed FTS-files
 DESCRIPTION:

 CALLING SEQUENCE:
	Result= READFILE ( rdir, filename, ext, head)

 CATEGORY:
	reduction MPFS-data

 INPUTS:
	rdir - string name input directory for reading
	filename - string name file withot extention
	ext -	string name extention file for reading (value '.zip' or '.fts')
		if extention e.q. '.zip' routine unzippiped files
 OUTPUTS:
	Result = 2D ploat point array MPFS-image

 OPTIONAL OUTPUT:
	head - string array contain FITS-header image

 OPTIONAL INPUT KEYWORDS:
	no

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	READ_FTS, SPAWN

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\readfile.pro)


READFITS

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	READFITS
 PURPOSE:
	Read a FITS file into IDL data and header variables. Will also
	read gzip compressed FITS files on Unix machines.

 CALLING SEQUENCE:
	Result = READFITS( Filename,[ Header, /NOSCALE, EXTEN_NO = ,
			/SILENT , NaNVALUE = , STARTROW = , NUMROW = ] )

 INPUTS:
	FILENAME = Scalar string containing the name of the FITS file  
		(including extension) to be read.   If the filename has
		a *.gz extension, it will be treated as a gzip compressed
		file.  

 OUTPUTS:
	Result = FITS data array constructed from designated record.
		If the specified file was not found, then Result = -1

 OPTIONAL OUTPUT:
	Header = String array containing the header from the FITS file.

 OPTIONAL INPUT KEYWORDS:
	NOSCALE - If present and non-zero, then the ouput data will not be
		scaled using the optional BSCALE and BZERO keywords in the 
		FITS header.   Default is to scale.

	SILENT - Normally, READFITS will display the size the array at the
		terminal.  The SILENT keyword will suppress this

	NaNVALUE - This scalar is only needed on VMS architectures.   It 
		specifies the value to translate any IEEE "not a number"
		values in the FITS data array.   It is needed because
		the VMS does not recognize the "not a number" convention.

	EXTEN_NO - scalar integer specify the FITS extension to read.  For
		example, specify EXTEN = 1 or /EXTEN to read the first 
		FITS extension.    Extensions are read using recursive
		calls to READFITS.

	POINT_LUN  -  Position (in bytes) in the FITS file at which to start
		reading.   Useful if READFITS is called by another procedure
		which needs to directly read a FITS extension.    Should 
		always be a multiple of 2880.

	STARTROW - This keyword only applies when reading a FITS extension
		It specifies the row (scalar integer) of the extension table at
		which to begin reading. Useful when one does not want to read 
		the entire table.

	NUMROW -  This keyword only applies when reading a FITS extension. 
		If specifies the number of rows (scalar integer) of the 
		extension table to read.   Useful when one does not want to
		read the entire table.

 EXAMPLE:
	Read a FITS file TEST.FITS into an IDL image array, IM and FITS 
	header array, H.   Do not scale the data with BSCALE and BZERO.

		IDL> im = READFITS( 'TEST.FITS', h, /NOSCALE)

	If the file contain a FITS extension, it could be read with

		IDL> tab = READFITS( 'TEST.FITS', htab, /EXTEN )

	The function TBGET() can be used for further processing of a binary 
	table, and FTGET for an ASCII table.
	To read only rows 100-149 of the FITS extension,

		IDL> tab = READFITS( 'TEST.FITS', htab, /EXTEN, 
					STARTR=100, NUMR = 50 )

	To read in a file that has been compressed:

		IDL> tab = READFITS('test.fits.gz',h)

 ERROR HANDLING:
	If an error is encountered reading the FITS file, then 
		(1) the system variable !ERROR is set (via the MESSAGE facility)
		(2) the error message is displayed (unless /SILENT is set),
			and the message is also stored in !ERR_STRING
		(3) READFITS returns with a value of -1
 RESTRICTIONS:
	(1) Cannot handle random group FITS
	(2) Cannot read the heap area in a variable length binary table

 NOTES:
	The procedure FXREAD can be used as an alternative to READFITS.
	FXREAD has the option of reading a subsection of the primary FITS data.

 PROCEDURES USED:
	Functions:   SXPAR(), WHERENAN()
	Procedures:  IEEE_TO_HOST, SXADDPAR, FDECOMP

 MODIFICATION HISTORY:
	MODIFIED, Wayne Landsman  October, 1991
	Added call to TEMPORARY function to speed processing     Feb-92
	Added STARTROW and NUMROW keywords for FITS tables       Jul-92
	Work under "windows"   R. Isaacman                       Jan-93
	Check for SIMPLE keyword in first 8 characters           Feb-93
	Removed EOF function for DECNET access                   Aug-93
	Work under "alpha"                                       Sep-93
       Null array processing fixed:  quotes in a message 
          properly nested, return added.  Affected case when
          readfits called from another procedure.   R.S.Hill    Jul-94
	Correct size of variable length binary tables W.Landsman Dec-94
	To read in compressed files on Unix systems. J. Bloch	 Jan-95
	Check that file is a multiple of 2880 bytes              Aug-95
	Added FINDFILE check for file existence K.Feggans        Oct-95
	Consistent Error Handling W. Landsman                    Nov-95
	Handle gzip image extensions  W. Landsman                Apr-96
	Fixed bug reading 1-d data introduced Apr-96 W. Landsman Jun-96

(See d:\rsi\idl40\mpfs.lib\READFITS.PRO)


READ_FTS

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	READ_FTS
 PURPOSE:
	Read a FITS file into IDL data and header variables. Will also
	read gzip compressed FITS files on Unix machines.

 CALLING SEQUENCE:
	Result = READ_FTS( Filename,[ Header, /NOSCALE, EXTEN_NO = ,
			/SILENT , NaNVALUE = , STARTROW = , NUMROW = ] )

 INPUTS:
	FILENAME = Scalar string containing the name of the FITS file  
		(including extension) to be read.   If the filename has
		a *.gz extension, it will be treated as a gzip compressed
		file.  

 OUTPUTS:
	Result = FITS data array constructed from designated record.
		If the specified file was not found, then Result = -1

 OPTIONAL OUTPUT:
	Header = String array containing the header from the FITS file.

 OPTIONAL INPUT KEYWORDS:
	NOSCALE - If present and non-zero, then the ouput data will not be
		scaled using the optional BSCALE and BZERO keywords in the 
		FITS header.   Default is to scale.

	SILENT - Normally, READFITS will display the size the array at the
		terminal.  The SILENT keyword will suppress this

	NaNVALUE - This scalar is only needed on VMS architectures.   It 
		specifies the value to translate any IEEE "not a number"
		values in the FITS data array.   It is needed because
		the VMS does not recognize the "not a number" convention.

	EXTEN_NO - scalar integer specify the FITS extension to read.  For
		example, specify EXTEN = 1 or /EXTEN to read the first 
		FITS extension.    Extensions are read using recursive
		calls to READFITS.

	POINT_LUN  -  Position (in bytes) in the FITS file at which to start
		reading.   Useful if READFITS is called by another procedure
		which needs to directly read a FITS extension.    Should 
		always be a multiple of 2880.

	STARTROW - This keyword only applies when reading a FITS extension
		It specifies the row (scalar integer) of the extension table at
		which to begin reading. Useful when one does not want to read 
		the entire table.

	NUMROW -  This keyword only applies when reading a FITS extension. 
		If specifies the number of rows (scalar integer) of the 
		extension table to read.   Useful when one does not want to
		read the entire table.

 EXAMPLE:
	Read a FITS file TEST.FITS into an IDL image array, IM and FITS 
	header array, H.   Do not scale the data with BSCALE and BZERO.

		IDL> im = READFITS( 'TEST.FITS', h, /NOSCALE)

	If the file contain a FITS extension, it could be read with

		IDL> tab = READFITS( 'TEST.FITS', htab, /EXTEN )

	The function TBGET() can be used for further processing of a binary 
	table, and FTGET for an ASCII table.
	To read only rows 100-149 of the FITS extension,

		IDL> tab = READFITS( 'TEST.FITS', htab, /EXTEN, 
					STARTR=100, NUMR = 50 )

	To read in a file that has been compressed:

		IDL> tab = READFITS('test.fits.gz',h)

 ERROR HANDLING:
	If an error is encountered reading the FITS file, then 
		(1) the system variable !ERROR is set (via the MESSAGE facility)
		(2) the error message is displayed (unless /SILENT is set),
			and the message is also stored in !ERR_STRING
		(3) READFITS returns with a value of -1
 RESTRICTIONS:
	(1) Cannot handle random group FITS
	(2) Cannot read the heap area in a variable length binary table

 NOTES:
	The procedure FXREAD can be used as an alternative to READFITS.
	FXREAD has the option of reading a subsection of the primary FITS data.

 PROCEDURES USED:
	Functions:   SXPAR(), WHERENAN()
	Procedures:  IEEE_TO_HOST, SXADDPAR, FDECOMP

 MODIFICATION HISTORY:
	MODIFIED, Wayne Landsman  October, 1991
	Added call to TEMPORARY function to speed processing     Feb-92
	Added STARTROW and NUMROW keywords for FITS tables       Jul-92
	Work under "windows"   R. Isaacman                       Jan-93
	Check for SIMPLE keyword in first 8 characters           Feb-93
	Removed EOF function for DECNET access                   Aug-93
	Work under "alpha"                                       Sep-93
       Null array processing fixed:  quotes in a message 
          properly nested, return added.  Affected case when
          readfits called from another procedure.   R.S.Hill    Jul-94
	Correct size of variable length binary tables W.Landsman Dec-94
	To read in compressed files on Unix systems. J. Bloch	 Jan-95
	Check that file is a multiple of 2880 bytes              Aug-95
	Added FINDFILE check for file existence K.Feggans        Oct-95
	Consistent Error Handling W. Landsman                    Nov-95
	Handle gzip image extensions  W. Landsman                Apr-96
	Fixed bug reading 1-d data introduced Apr-96 W. Landsman Jun-96
	MODIFIED for MPFS FITS-format by Victor Afanasiev	 Jul-99

(See d:\rsi\idl40\mpfs.lib\read_fts.pro)


REDUCTION

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	REDUCTION
 PURPOSE:
	bias substraction,replace bad pixels, remove cosmic hits and 
	correction flexibility in set MPFS-image with different type
 DESCRIPTION: 
	Routine make bias substraction,replace bad pixels, remove cosmic hits and 
	correction flexibility in set MPFS-image with different type.
	image shiftted at differnt way for different value image_type:
	obj and neon-images shifted relatively 1-st image in both direction,
	flat-images shifted relatively reduced obj-image  only in cross-dispersion 
	direction, star,eta and test-images  shifted relatively reduced flat-image 
	in cross-dispersion direction. Routine modified FITS-header saved FITS-files
	
 CALLING SEQUENCE:
	REDUCTION, LOGFILE, image_type, SHIFT=shift
	
 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	image_type = string array type of exposure (values: 'bias','obj','star',
				'flat','eta','neon','test')
		  	

 OUTPUTS:
	Result saved at working directory in file '*_i.fts',where '*'=image_type
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	SHIFT  if keyword preset image to be shiftted

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function  DEF_WDIR, DEF_RDIR, DEF_NAME, READFILE, READ_FTS,
		  COSMETIC, DEF_SHIFT, SHIFT_IMAGE
	Procedure SXADDPAR, SXADDHIST, REM_HITS

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\reduct.pro)


REM_HITS

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	REM_HITS
 PURPOSE:
	remove cosmic hits on exposure frames
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = REM_HITS ( obj_spp, NOSMOOTH=nosmooth)
 CATEGORY:
	reduction MPFS-data		

INPUTS :
      obj_spp - set of analised images

 OUTPUTS:
	Result = total image cleaned at cosmic hits 
		
 OPTIONAL OUTPUT:
	obj_spp - set of  images cleaned at cosmic hits 

 OPTIONAL INPUT KEYWORDS:
	NOSMOOTH if keyword present, data not smoothed along dispersion	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	ROBOMEAN

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\rem_hits.pro)


RFIX

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	RFIX

 PURPOSE:
	Round X to its nearest integer.

 CALLING SEQUENCE:
	Result = RFIX(X)

 INPUT:
	X = number, vector or array to be rounded.

 KEYWORDS:
	LONG = if set, it will round to a longword integer.

 OUTPUT:
	Result = nearest integer rounded version of X.

 SIDE EFFECTS:
	None.

 COMMON BLOCKS:
	None.

 RESTRICTIONS:
	None.

 PROCEDURE:
	Straightforward. Algorithm is faster than ASTROLIB NINT function.

 MODIFICATION HISTORY:
	Written by Roberto Luis Molowny Horas, November 1991.

(See d:\rsi\idl40\mpfs.lib\rfix.pro)


ROBOMEAN

[Previous Routine] [Next Routine] [List of Routines]
 NAME:  
	robomean  
 PURPOSE: (one line)  
	Robust statistical moments of the data.  
 DESCRIPTION:  
       This routine computes the average, average deviation, standard  
       deviation, variance, skew and kurtosis of the input data.  The various  
       output quantities are always returned as floating point scalars.  
       The statistics are computed with no regard for the dimensionality of  
       the input data.  
  
	The statistics are robust in that the data is searched for outliers  
	after the moments are computed.  If outliers are found they are  
	removed and the statistics are computed again.  This continues until  
	either no outliers are found or if the removal of outliers has an  
	insignificant effect on the statistics.  
 CATEGORY:  
	statistics  
 CALLING SEQUENCE:  
	robomean,data,thresh,eps,avg,avgdev,stddev,var,skew,kurt,nfinal  
 INPUTS:  
       data   - Input data to be analyzed.  
	thresh - Deviation from the mean to signify an outlier.  
	eps    - Smallest significant change in mean in units of std dev.  
 OPTIONAL INPUT PARAMETERS:  
       None.  
 INPUT KEYWORD PARAMETERS:  
       None.  
 OUTPUT KEYWORD PARAMETERS:  
       STDMEAN : Optional return of standard deviation of the mean.  
 OUTPUTS:  
       avg    - Sample mean.  
       avgdev - Average deviation of the data from the mean.  
       stddev - Standard deviation of the data from the mean.  
       var    - Variance of the data from the mean.  
       skew   - Skewness, third statistical moment.  
       kurt   - Kurtosis, fourth statistical moment.  
       nfinal - Number of points used in the final result.  
       new    - Vector of 'clean' pixels (optional).  
 COMMON BLOCKS:  
       None.  
 SIDE EFFECTS:  
       None.  
 RESTRICTIONS:  
       None.  
 PROCEDURE:  
       Standard techniques, see section 13.1 in Numerical Recipies.  The  
	thresh and eps values are not tremendously important.  Thresh=5.0  
	and eps=0.5 appear to work pretty well most of the time.  
 MODIFICATION HISTORY:  
       Written by Marc W. Buie, Lowell Observatory, 1992 Jan 20.  
       Fix - nfinal was not being returned to calling program.  
             Doug Loucks, Lowell Observatory, 1992 Oct 22.  
       Fix - Sense of test to determine additional refinement was  
             not correct for some cases.  Changed logic to parallel  
             the C version, since the WHILE statement is now available  
             in IDL.  
       Mod - Added by Marc Buie: Argument 'new,' allowing the 'clean' pixels  
             to be returned to the caller.  
       Mod - 2/11/94, DWL, Added keyword STDMEAN to permit return of this  
             value to the caller. 
	Modified for MPFS-data by Victor Afanasiev, Jul 1999 

(See d:\rsi\idl40\mpfs.lib\robomean.pro)


SCATTER

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SCATTER
 PURPOSE:
	substraction scattering ligth
 DESCRIPTION: 
	Routine estimate level scattering light outside of first and
	last traectory etalon spectra and substracted scattering light
	
 CALLING SEQUENCE:
	Result=SCATTER ( image, traectory_eta)

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	image - input MPFS image
	traectory_tra - 2D array traectories etalon spectra
	
 OUTPUTS:
	Result = scattering ligth substracted image
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	GOODPOLY

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\scatter.pro)


SHIFT_IMAGE

[Previous Routine] [Next Routine] [List of Routines]
 NAME:        
	 SHIFT_IMAGE
 PURPOSE:      Remap image by linear interpolation
 CATEGORY:
 CALLING SEQUENCE:
       In = shift_image(im,dx,dy)
 INPUTS:
       Im	= Image to be shifted
	Dx	= Shift in X-direction
	Dy	= Shift in Y-direction
 KEYWORD PARAMETERS:

 OUTPUTS:
       In
 COMMON BLOCKS:
       None.
 SIDE EFFECTS:

 RESTRICTIONS:

 PROCEDURE:

 MODIFICATION HISTORY:
       Z. Yi, UiO, June, 1992.
	modified for MPFS-data by Victor Afanasiev, Jul 1999

(See d:\rsi\idl40\mpfs.lib\shift_im.pro)


SHIFT_S

[Previous Routine] [Next Routine] [List of Routines]
 NAME:        
	 SHIFT_S
 PURPOSE:      Remap spectrum by linear interpolation
 CATEGORY:
 CALLING SEQUENCE:
       In = shift_s ( Vector , dx )
 INPUTS:
       Vector	= Image to be shifted
	Dx	= Shift in X-direction
 KEYWORD PARAMETERS:

 OUTPUTS:
       In
 COMMON BLOCKS:
       None.
 SIDE EFFECTS:

 RESTRICTIONS:

 PROCEDURE:

 MODIFICATION HISTORY:
     Written by Victor Afanasiev, Special Astrophisical observatory,  July, 1999.

(See d:\rsi\idl40\mpfs.lib\shift_s.pro)


SHOW_3

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SHOW_3
 PURPOSE:
	visualisation 3 images :  obj_s.fts, obj_lin.fts, obj-sky.fts
 DESCRIPTION:

 CALLING SEQUENCE:
	SHOW_3, LOGFILE, PS=ps

 CATEGORY:
	reduction MPFS-data

 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)

 OUTPUTS:
	no

 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	PS - if keyword preset plot image print in POSTSCRIPT file
	     in working directory (standard name image_3.ps)

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	Function 	- DEF_NAME,
	Procedure	- SXPAR

 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\show_3.pro)


SPEXTR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SPEXTR
 PURPOSE:
	extraction spectra in MPFS-image
 DESCRIPTION: 
	
 CALLING SEQUENCE:
	Result = SPEXTR ( image , traectory , fwhm )

 CATEGORY:
	reduction MPFS-data		

 INPUTS:
	image - input image (2D float point array)
	traectory - 2D array traectory spectra
	fwhm - width of the strobe

 OUTPUTS:
	Result =2D array spectra
		
 OPTIONAL OUTPUT:
	no

 OPTIONAL INPUT KEYWORDS:
	no	

 RESTRICTIONS:
	no

 NOTES:
	no

 PROCEDURES USED:
	;
 MODIFICATION HISTORY:
       Written by Victor Afanasiev, Special Astrophysical Observatory RAS, Jul 1999

(See d:\rsi\idl40\mpfs.lib\spextr.pro)


STRN

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	STRN
 PURPOSE:
	The main and original purpose of this procedure is to convert a number
	to an unpadded string (i.e. with no blanks around it.)  However, it 
	has been expanded to be a multi-purpose formatting tool.  You may 
	specify a length for the output string; the returned string is either 
	set to that length or padded to be that length.  You may specify 
	characters to be used in padding and which side to be padded.  Finally,
	you may also specify a format for the number.  NOTE that the input 
	"number" need not be a number; it may be a string, or anything.  It is
	converted to string.

 CALLING SEQEUNCE:
	tmp = STRN( number, [ LENGTH=, PADTYPE=, PADCHAR=, FORMAT = ] )

 INPUT:
	NUMBER    This is the input variable to be operated on.  Traditionally,
		 it was a number, but it may be any scalar type.

 OPTIONAL INPUT:
	LENGTH    This KEYWORD specifies the length of the returned string.  
		If the output would have been longer, it is truncated.  If 
		the output would have been shorter, it is padded to the right 
		length.
	PADTYPE   This KEYWORD specifies the type of padding to be used, if any.
		0=Padded at End, 1=Padded at front, 2=Centered (pad front/end)
		IF not specified, PADTYPE=1
	PADCHAR   This KEYWORD specifies the character to be used when padding.
		The default is a space (' ').
	FORMAT    This keyword allows the FORTRAN type formatting of the input
		number (e.g. '(f6.2)')

 OUTPUT:
	tmp       The formatted string

 USEFUL EXAMPLES:
	print,'Used ',strn(stars),' stars.'  ==> 'Used 22 stars.'
	print,'Attempted ',strn(ret,leng=6,padt=1,padch='0'),' retries.'
		==> 'Attempted 000043 retries.'
	print,strn('M81 Star List',length=80,padtype=2)
		==> an 80 character line with 'M81 Star List' centered.
	print,'Error: ',strn(err,format='(f15.2)')
		==> 'Error: 3.24'     or ==> 'Error: 323535.22'

 HISTORY:
	03-JUL-90 Version 1 written by Eric W. Deutsch
	10-JUL-90 Trimming and padding options added         (E. Deutsch)
	29-JUL-91 Changed to keywords and header spiffed up     (E. Deutsch)
	Ma7 92 Work correctly for byte values (W. Landsman)
	19-NOV-92 Added Patch to work around IDL 2.4.0 bug which caused an
	error when STRN('(123)') was encountered.            (E. Deutsch)

(See d:\rsi\idl40\mpfs.lib\STRN.PRO)


STRNUMBER

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	STRNUMBER
 PURPOSE:
	Function to determine if a string is a valid numeric value.

 CALLING SEQUENCE:
	result = strnumber( st, [val] )

 INPUTS:
	st - any IDL scalar string

 OUTPUTS:
	1 is returned as the function value if the string st has a
	valid numeric value, otherwise, 0 is returned.

 OPTIONAL OUTPUT:
	val - (optional) value of the string.  real*8

 WARNING:
	(1)   In V2.2.2 there was a bug in the IDL ON_IOERROR procedure that
	      will cause the following statement to hang up IDL

	      IDL> print,'' + string( strnumber('xxx') )
	      This bug was fixed in V2.3.0
	(2)   In V2.3.2, an IDL bug is seen in the following statements 
	      IDL> st = 'E'
	      IDL> q = strnumber(st)  & print,st
	      The variable 'st' gets modified to an empty string.   This problem
	      is related to the ambiguity of whether 'E' is a number or not 
	      (could be = 0.0E).    This bug was fixed in V3.0.0
	(3)   STRNUMBER was modified in February 1993 to include a special 
	      test for empty or null strings, which now returns a 0 (not a 
	      number).     Without this special test, it was found that a
	      empty string (' ') could corrupt the stack.
 HISTORY:
	version 1  By D. Lindler Aug. 1987
       test for empty string, W. Landsman          February, 1993

(See d:\rsi\idl40\mpfs.lib\STRNUMBE.PRO)


SUB_NSKY

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SUB_NSKY
 PURPOSE:
	substraction nigth sky spectrum in MPFS data

 CALLING SEQUENCE:
	Result = SUB_NSKY, LOGFILE, image_name, [LINE='line']
 INPUTS:
	LOGFILE = file name of LOG observation (in format FITS-header)
	image_name = string scalar type of exposure values '*'= 'obj' or 'star'
			or 'test'
	routine read in working directory coefficients dispersion
	curves (file 'disper.fts'), extracted linearised spectra 
	object (file '*_lin.fts') and nigth sky probe (file '*_ns.fts)
 OUTPUTS:
	 saved in file  '*-sky.fts'
 OPTIONAL OUTPUT:
	no
 OPTIONAL INPUT KEYWORDS:
	LINE - use separate nigth sky line for determination accuracy
		sky substraction
	PLOT - on control plotting
 ERROR HANDLING:
	no
 RESTRICTIONS:
	no
 NOTES:
	no
 PROCEDURES USED:
	Functions:  SPEXTR, PAR_LINE, LINEAR,READ_FTS
	Pricedure:  SXADDPAR
 MODIFICATION HISTORY:
	MODIFIED by Victor Afanasiev, Special Astrophysical Observatory  July, 1999

(See d:\rsi\idl40\mpfs.lib\sub_nsky.pro)


SXADDHIST

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SXADDHIST                           
 PURPOSE:
	Procedure to add history line(s) to a FITS or STSDAS header

 CALLING SEQUENCE
	sxaddhist, history, header, [ /PDU ]

 INPUTS:
	history - string or string array containing history line(s)
		to add to the header
	header - string array containing the FITS or STSDAS header

 KEYWORD INPUTS:
	/PDU - if specified, the history will be added to the primary
		data unit header, (before the line beginning BEGIN EXTENSION...)
		Otherwise, it will be added to the end of the header
 OUTPUTS:
	header - unpdated header

 EXAMPLES:
	sxaddhist, 'I DID THIS', header

	hist = strarr(3)
	hist(0) = 'history line number 1'
	hist(1) = 'the next history line'
	hist(2) = 'the last history line'
	sxaddhist, hist, header

 HISTORY:
	D. Lindler  Feb. 87
	April 90  Converted to new idl  D. Lindler
	Put only a single space after HISTORY   W. Landsman  November 1992
	Aug. 95	  Added PDU keyword parameters

(See d:\rsi\idl40\mpfs.lib\SXADDHIS.PRO)


SXADDPAR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SXADDPAR
 PURPOSE:
	Add or modify a parameter in a FITS or STSDAS header array.

 CALLING SEQUENCE:
	sxaddpar, Header, Name, Value, [ Comment,  Location,
				BEFORE =, AFTER = , FORMAT= , /PDU]

 INPUTS:
	Header = String array containing FITS or STSDAS header.    The
		length of each element must be 80 characters.    If not 
		defined, then SXADDPAR will create an empty FITS header array.

	Name = Name of parameter. If Name is already in the header the value 
		and possibly comment fields are modified.  Otherwise a new 
		record is added to the header.  If name = 'HISTORY' then the 
		value will be added to the record without replacement.  In 
		this case the comment parameter is ignored.

	Value = Value for parameter.  The value expression must be of the 
		correct type, e.g. integer, floating or string.  String values
		 of 'T' or 'F' are considered logical values.

 OPTIONAL INPUT PARAMETERS:
	Comment = String field.  The '/' is added by this routine.  Added 
		starting in position 31.    If not supplied, or set equal to 
		'', then the previous comment field is retained (when found) 

	Location = Keyword string name.  The parameter will be placed before the
		location of this keyword.    This parameter is identical to
		the BEFORE keyword and is kept only for consistency with
		earlier versions of SXADDPAR.

 OPTIONAL INPUT KEYWORD PARAMETERS:
	BEFORE	= Keyword string name.  The parameter will be placed before the
		location of this keyword.  For example, if BEFORE='HISTORY'
		then the parameter will be placed before the first history
		location.  This applies only when adding a new keyword;
		keywords already in the header are kept in the same position.

	AFTER	= Same as BEFORE, but the parameter will be placed after the
		location of this keyword.  This keyword takes precedence over
		BEFORE.

	FORMAT	= Specifies FORTRAN-like format for parameter, e.g. "F7.3".  A
		scalar string should be used.  For complex numbers the format
		should be defined so that it can be applied separately to the
		real and imaginary parts.
	/PDU    = specifies keyword is to be added to the primary data unit
		header. If it already exists, it's current value is updated in
		the current position and it is not moved.
 OUTPUTS:
	Header = updated FITS header array.

 RESTRICTIONS:
	Warning -- Parameters and names are not checked
		against valid FITS parameter names, values and types.

 MODIFICATION HISTORY:
	DMS, RSI, July, 1983.
	D. Lindler Oct. 86  Added longer string value capability
	Converted to NEWIDL  D. Lindler April 90
	Added Format keyword, J. Isensee, July, 1990
	Added keywords BEFORE and AFTER. K. Venkatakrishna, May '92
	Pad string values to at least 8 characters   W. Landsman  April 94
	Aug 95: added /PDU option and changed routine to update last occurence
		of an existing keyword (the one SXPAR reads) instead of the
		first occurence.

(See d:\rsi\idl40\mpfs.lib\SXADDPAR.PRO)


SXDELPAR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SXDELPAR
 PURPOSE:
	Procedure to delete a keyword parameter(s) from a FITS or STSDAS header

 CALLING SEQUENCE:
	sxdelpar, h, parname

 INPUTS:
	h - FITS or STSDAS header, string array
	parname - string or string array of keyword name(s) to delete

 OUTPUTS:
	h - updated FITS or STSDAS header, If all lines are deleted from 
		the header, then h is returned with a value of 0

 EXAMPLE:
	Delete the astrometry keywords CDn_n from a FITS header, h

	IDL> sxdelpar, h, ['CD1_1','CD1_2','CD2_1','CD2_2']

 NOTES:
	(1)  No message is returned if the keyword to be deleted is not found
	(2)  All appearances of a keyword in the header will be deleted
 HISTORY:
	version 1  D. Lindler Feb. 1987
	Converted to new IDL  April 1990 by D. Lindler
	Test for case where all keywords are deleted    W. Landsman Aug 1995 

(See d:\rsi\idl40\mpfs.lib\SXDELPAR.PRO)


SXPAR

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
	SXPAR
 PURPOSE:
	Obtain the value of a parameter in a FITS or STSDAS header

 CALLING SEQUENCE:
	result = SXPAR( Hdr, Name, [ Abort, COUNT=, COMMENT =  ])   

 INPUTS:
	Hdr =  FITS or STSDAS header array, (e.g. as returned by READFITS or 
		SXOPEN) string array, each element should have a length of 80
		characters	

	Name = String name of the parameter to return.   If Name is of 
		the form 'keyword*' then an array is returned containing 
		values of keywordN where N is an integer.  The value
		of keywordN will be placed in RESULT(N-1).  The data type 
		of RESULT will be the type of the first valid match of keywordN 
		found.

 OPTIONAL INPUTS:
	ABORT - string specifying that SXPAR should do a RETALL
		if a parameter is not found.  ABORT should contain
		a string to be printed if the keyword parameter is not found.
		If not supplied SXPAR will return with a negative
		!err if a keyword is not found.

 OPTIONAL OUTPUT KEYWORDS:
	COUNT - Optional keyword to return a value equal to the number of 
		parameters found by sxpar, integer scalar

	COMMENT - Array of comments associated with the returned values

 OUTPUTS:
	Function value = value of parameter in header.
		If parameter is double precision, floating, long or string,
		the result is of that type.  Apostrophes are stripped
		from strings.  If the parameter is logical, 1 is
		returned for T, and 0 is returned for F.
		If Name was of form 'keyword*' then a vector of values
		are returned.

 SIDE EFFECTS:
	!ERR is set to -1 if parameter not found, 0 for a scalar
	value returned.  If a vector is returned it is set to the
	number of keyword matches found.

	If a keyword occurs more than once in a header, a warning is given,
	and the first occurence is used.

 EXAMPLES:
	Given a FITS header, h, return the values of all the NAXISi values
	into a vector.    Then place the history records into a string vector.

	IDL> naxisi = sxpar( h ,'NAXIS*')         ; Extract NAXISi value
	IDL> history = sxpar( h, 'HISTORY' )      ; Extract HISTORY records

 PROCEDURE:
	The first 8 chacters of each element of Hdr are searched for a 
	match to Name.  The value from the last 20 characters is returned.  
	An error occurs if there is no parameter with the given name.
       
	If a numeric value has no decimal point it is returned as type
	LONG.   If it contains more than 8 numerals, or contains the 
	character 'D', then it is returned as type DOUBLE.  Otherwise
	it is returned as type FLOAT

 MODIFICATION HISTORY:
	DMS, May, 1983, STPAR Written.
	D. Lindler Jan 90 added ABORT input parameter
	J. Isensee Jul,90 added COUNT keyword
	W. Thompson, Feb. 1992, added support for FITS complex values.
	W. Thompson, May 1992, corrected problem with HISTORY/COMMENT/blank
		keywords, and complex value error correction.
	W. Landsman, November 1994, fix case where NAME is an empty string 
	W. Landsman, March 1995,  Added COMMENT keyword, ability to read
		values longer than 20 character
	W. Landsman, July 1995, Removed /NOZERO from MAKE_ARRAY call

(See d:\rsi\idl40\mpfs.lib\SXPAR.PRO)


WRITEFITS

[Previous Routine] [List of Routines]
 NAME:
	WRITEFITS
 PURPOSE:
	Write an an IDL array into a disk FITS file.    Works with all types
	of FITS files except random groups

 CALLING SEQUENCE:
	WRITEFITS, filename, data [, header, NaNvalue = , /APPEND] 

 INPUTS:
	FILENAME = String containing the name of the file to be written.

	DATA = Image array to be written to FITS file.    If DATA is 
              undefined or a scalar, then only the FITS header (which
              must have NAXIS = 0) will be written to disk

 OPTIONAL INPUT:
	HEADER = String array containing the header for the FITS file.
		 If variable HEADER is not given, the program will generate
		 a minimal FITS header.

 OPTIONAL INPUT KEYWORD:
       NaNvalue - Value in the data array to be set to the IEEE NaN
                 condition.   This is the FITS representation of undefined
                 values 
       APPEND - If this keyword is set then the supplied header and data
                array are assumed to be an extension and are appended onto
                the end of an existing FITS file.    Note that the primary
                header in the existing file must already have an EXTEND
                keyword to indicate the presence of an FITS extension.

 OUTPUTS:
	None

 RESTRICTIONS:
       (1) It recommended that BSCALE and BZERO not be used (or set equal
           to 1. and 0) with REAL*4 or REAL*8 data.
       (2) WRITEFITS will remove any group parameters from the FITS header

 EXAMPLE:
       Write a randomn 50 x 50 array as a FITS file creating a minimal header.

       IDL> im = randomn(seed, 50, 50)        ;Create array
       IDL> writefits, 'test', im             ;Write to a FITS file "test"

 PROCEDURES USED:
       CHECK_FITS, HOST_TO_IEEE, IS_IEEE_BIG(), SXDELPAR, SXADDPAR, SXPAR()

 MODIFICATION HISTORY:
	WRITTEN, Jim Wofford, January, 29 1989
       MODIFIED, Wayne Landsman, added BITPIX = -32,-64 support for UNIX
       Use new BYTEODER keywords 22-Feb-92
       Modify OPENW for V3.0.0   W. Landsman       Dec 92
       Work for "windows"   R. Isaacman            Jan 93
	More checks for null data                   Mar 94
	Work for Linux  W. Landsman                 Sep 95
	Added call to IS_IEEE_BIG()  W. Landsman  Apr 96

(See d:\rsi\idl40\mpfs.lib\WRITEFIT.PRO)