;+
;$Id: generate_ipt.pro,v 1.14 2011/07/19 16:09:43 nathan Exp $
;
; Project     : STEREO - SECCHI 
;                   
; Name        : GENERATE_IPT
;               
; Purpose     : Routine to output the schedule in IPT form.
;               
; Explanation : This routine prints out the current schedule in IPT format
;		in form of keyword/value pairs. 
;               
; Use         : GENERATE_IPT, startime, endtime, ipt_name
;    
; Inputs      : startime  Schedule start time
;               endtime   Schedule end time 
;               
; Opt. Inputs : None.
;               
; Outputs     : ipt_name  Schedule start and times are used to form the .IPT filename
;                         (and used to generate the .IPT file).
;               
; Opt. Outputs: None. 
;               
; Keywords    : EXPAND_BSF IF present, Does not collapse BSF entries into one section. 
;
; Category    : Planning, Scheduling.
;               
; Prev. Hist. : Based on SOHO/LASCO planning tool. 
;
; Written by  : Ed Esfandiari, NRL, May 2004 - First Version.
;
; Modification History:
;              Ed Esfandiari 06/07/04 - Print os_num using 4-digits.
;                            06/15/04 - Added PT_OS_PROCT (processing time) parameter.
;                            06/16/04 - Added PT_OS_SETUP (setup time) parameter.
;                            06/30/04 - Used expanded os_start to pickup img_cntr, seq_cntr, and sfn.
;                            07/14/04 - Use 4 ROI tables instead of 1. Also added cl_time and ro_time.
;                            07/19/04 - report same cnt non-seq img_cntr when schedule is multi-days.
;                            08/31/04 - Changed format of exptime reports.
;                            09/27/04 - Added PT_SC_ID.
;                            09/30/04 - Removed sync. Added real set_id values to output.
;                            10/04/04 - Write IPT to directories SC_A, SC_B, or SC_AB.
;                            10/05/04 - Handle cmdseq files for SC_A and SC_B.
;              Ed Esfandiari 10/06/04 - Added GT dump SpaceCraft dependency.
;              Ed Esfandiari 10/12/04 - Added pre/post schedule door open/close times in .IPT. 
;              Ed Esfandiari 11/08/04 - Added expand_bsf keyword. If not set, OSes in cmdseq
;                                       will collapse into a .bsf entry in .IPT file. 
;              Ed Esfandiari 11/16/04 - Added SCIP door conflict checks.
;                            12/02/04 - Added door closure overlap detection.
;              Ed Esfandiari 12/13/04 - Report non cal image exptimes corrected for CCD summing.
;              Ed Esfandiari 01/10/05 - correct non-calib exptime for lowgain. 
;              Ed Esfandiari 02/03/05 - Added I (Init Timeline) command to IPT output.
;              Ed Esfandiari 05/03/05 - Added A (Run Script) command to IPT output.
;              Ed Esfandiari 05/09/05 - Modified to allow multiple init timeline commands.
;              Ed Esfandiari 05/11/05 - Modified to allow multiple Run Script commands.
;              Ed Esfandiari 05/24/05 - Use ccd orientation dependant masks.
;              Ed Esfandiari 11/22/05 - Removed sfn from IPT since they are not used.
;              Ed Esfandiari 12/07/05 - Keep uniq img_cnt (in case multiple apid is used).
;              Ed Esfandiari 02/27/06 - Break schedule into daily periods so that img_cntr
;                                       info which is reset to 1 at 00:00:00 hour on each day
;                                       for subsequent days are not lost if schedule expands
;                                       into next day(s).
;              Ed Esfandiari 05/10/06 - Added proc_times for multi_apids. Also keep first size and 
;                                       unique proc_times of OS in a sequence and changes size units from
;                                       from bits to bytes. In schedule_read*.pro since USEDEFAULTS = 1,
;                                       size, etc. are recalculated so things are fine. 
;              Ed Esfandiari 05/11/06 - Added table usage information to the IPT file.
;              Ed Esfandiari 05/23/06 - Added PT filename info and removed $ from table info.
;              Ed Esfandiari 05/23/06 - Added GT rates.
;              Ed Esfandiari 11/21/06 - Ignore ccd_sum and low gain exptime correction (FSW does not do it).
;              Ed Esfandiari 12/29/06 - Let GT-dumps be added to IPT file even with the expand_bsf keyword when needed.
;              Ed Esfandiari 06/17/08 - Added code to handle bsf files that don't contain any images.
;
;
; $Log: generate_ipt.pro,v $
; Revision 1.14  2011/07/19 16:09:43  nathan
; make /EXPAND_BSF the default; add /NO_EXPAND_BSF
;
; Revision 1.13  2009/09/11 20:28:10  esfand
; use 3-digit decimals to display volumes
;
; Revision 1.8  2006/04/06 15:23:30  esfand
; Break schedule into daily periods
;
; Revision 1.7  2005/12/16 14:58:51  esfand
; Commit as of 12/16/05
;
; Revision 1.6  2005/05/26 20:00:58  esfand
; PT version used to create SEC20050525005 TVAC schedule
;
; Revision 1.5  2005/03/10 16:42:06  esfand
; changes since Jan24-05 to Mar10-05
;
; Revision 1.4  2005/01/24 17:56:33  esfand
; checkin changes since SCIP_A_TVAC
;
; Revision 1.2  2004/09/01 15:40:43  esfand
; commit new version for Nathan.
;
; Revision 1.1.1.2  2004/07/01 21:19:01  esfand
; first checkin
;
; Revision 1.1.1.1  2004/06/02 19:42:35  esfand
; first checkin
;
;
;-

;__________________________________________________________________________________________________________
;
PRO ADD_DOOR_CMND,OUT,times,tel,dlp,spacecraft,schedv_sc

   IF (DATATYPE(times) NE 'DOU') THEN RETURN
   dtimes= times
   sc= spacecraft

   ocnt= N_ELEMENTS(dtimes)
   ok= INDGEN(ocnt)
   IF (schedv_sc EQ 1) THEN ok= WHERE(sc EQ 'A', ocnt)
   IF (schedv_sc EQ 2) THEN ok= WHERE(sc EQ 'B', ocnt) 
   IF (ocnt GT 0) THEN BEGIN
       dtimes= dtimes(ok)
       sc= sc(ok)
   ENDIF ELSE dtimes= -1


   IF (DATATYPE(dtimes) EQ 'DOU') THEN BEGIN
     ct= UTC2STR(TAI2UTC(dtimes),/ECS)

     ;IF (dlp EQ 8) THEN $ ; closed doors
     ;  kcd= WHERE(ct GT '2000/01/02', kcnt) $
     ;ELSE  $ ; open doors (dlp=9) 
     ;  kcd= WHERE(ct GT '2000/01/02' AND ct LT '3000/01/01', kcnt) 

     ;d2000= WHERE(ct EQ '2000', dcnt)
     d2000= WHERE(ct LT '2003/12/31', dcnt)
     IF (dcnt GT 0) THEN ct(d2000)= '2000/01/01 00:00:00.000'
     ;d3000= WHERE(ct EQ '3000', dcnt)
     d3000= WHERE(ct GT '2500/01/01', dcnt)
     IF (dcnt GT 0) THEN ct(d3000)= '3000/01/01 00:00:00.000'

     kcnt= N_ELEMENTS(ct)
     ;IF(kcnt GT 0) THEN BEGIN
       PRINTF, OUT, 'PT_OS_NUM = 0001'
       PRINTF, OUT, 'PT_LP_NUM = '+STRTRIM(dlp,2)    ; DOOR closed
       PRINTF, OUT, 'PT_LP_NSCHED = '+STRTRIM(kcnt,2)
       cstart= 'PT_LP_START = ('
       FOR i= 0, kcnt-1 DO BEGIN
         ;cstart= cstart + STRMID(ct(kcd(i)),0,4)+STRMID(ct(kcd(i)),5,2)+STRMID(ct(kcd(i)),8,2)+'_'+ $
         ;                 STRMID(ct(kcd(i)),11,2)+STRMID(ct(kcd(i)),14,2)+STRMID(ct(kcd(i)),17,2)
         cstart= cstart + STRMID(ct(i),0,4)+STRMID(ct(i),5,2)+STRMID(ct(i),8,2)+'_'+ $
                          STRMID(ct(i),11,2)+STRMID(ct(i),14,2)+STRMID(ct(i),17,2)
         IF (i LT kcnt-1) THEN $
           cstart= cstart + ',' $
         ELSE $
           cstart= cstart + ')'
       END
       PRINTF, OUT, cstart
       PRINTF, OUT, 'PT_TELE = '+STRTRIM(tel,2) 
       PRINTF, OUT, 'PT_LP_SC= ('+ARR2STR(sc)+')'
       PRINTF, OUT, ';'
       PRINTF, OUT, ';' 
     ;ENDIF
   ENDIF
   RETURN
END

PRO ADD_GT_CMND,OUT,stime,etime,apid, sc, lp, rate

   IF (DATATYPE(stime) EQ 'DOU') THEN BEGIN
     stm= UTC2STR(TAI2UTC(stime),/ECS)
     etm= UTC2STR(TAI2UTC(etime),/ECS)
     PRINTF, OUT, 'PT_OS_NUM = 0002'
     PRINTF, OUT, 'PT_LP_NUM = '+STRTRIM(lp,2)
     gcnt= N_ELEMENTS(stm)
     PRINTF, OUT, 'PT_LP_NSCHED = '+STRTRIM(gcnt,2)
     gstart= 'PT_LP_START = ('
     gend  = 'PT_LP_END   = ('
     gapid = 'PT_LP_APID  = ('
     gsc   = 'PT_LP_SC    = (' 
     grate = 'PT_GT_RATE  = ('
     FOR i= 0, gcnt-1 DO BEGIN
         gstart= gstart + STRMID(stm(i),0,4)+STRMID(stm(i),5,2)+STRMID(stm(i),8,2)+'_'+ $
                          STRMID(stm(i),11,2)+STRMID(stm(i),14,2)+STRMID(stm(i),17,2)
         gend=   gend   + STRMID(etm(i),0,4)+STRMID(etm(i),5,2)+STRMID(etm(i),8,2)+'_'+ $
                          STRMID(etm(i),11,2)+STRMID(etm(i),14,2)+STRMID(etm(i),17,2)
         gapid=  gapid  + STRTRIM(apid(i),2) 
         gsc=    gsc    + STRTRIM(sc(i),2) 
         grate=  grate  + STRTRIM(rate(i),2)
         
         IF (i LT gcnt-1) THEN BEGIN 
           gstart= gstart + ','
           gend= gend+ ','
           gapid= gapid+ ','
           gsc= gsc+','
           grate= grate+','
         ENDIF ELSE BEGIN 
           gstart= gstart + ')'
           gend= gend+ ')'
           gapid= gapid+ ')'
           gsc= gsc+ ')'
           grate= grate+ ')'
         ENDELSE
     END
     PRINTF, OUT, gstart
     PRINTF, OUT, gend
     PRINTF, OUT, gapid
     PRINTF, OUT, gsc
     PRINTF, OUT, grate
     PRINTF, OUT, ';'
     PRINTF, OUT, ';'
   ENDIF

   RETURN
END



FUNCTION CHK_DR_OLAPS, cdoor, odoor, tel, sc

   msg= ''
   n= N_ELEMENTS(cdoor)
   FOR i= 1, n-1 DO BEGIN
     IF (cdoor(i) LE odoor(i-1)) THEN BEGIN
       cls= UTC2STR(TAI2UTC(cdoor(i)),/TRUNCATE)
       opn= UTC2STR(TAI2UTC(odoor(i-1)),/TRUNCATE) 
       msg= 'Door Schedule Overlap: '+tel+' door open at '+opn+' and door close at '+cls+' . Command canceled - S/C - '+sc
       RETURN, msg
     ENDIF
   ENDFOR
   RETURN, msg
END



FUNCTION CHECK_DOOR_OVERLAPS,cdoors, odoors, tel, spacecraft, schedv_sc
COMMON DIALOG, mdiag,font

  msg= ''
  msg1= ''

  IF (cdoors(0) GT 0) THEN BEGIN
     sc= spacecraft
     cdoor= cdoors
     odoor= odoors

     CASE schedv_sc OF
      0: BEGIN
           dr= WHERE(spacecraft EQ 'A', drcnt)
           IF (drcnt GT 0) THEN BEGIN
             msg= CHK_DR_OLAPS(cdoor(dr), odoor(dr), tel, 'A')
           ENDIF
           dr= WHERE(spacecraft EQ 'B', drcnt)
           IF (drcnt GT 0) THEN BEGIN
             msg1= CHK_DR_OLAPS(cdoor(dr), odoor(dr), tel, 'B')
           ENDIF
         END
      1: BEGIN
           dr= WHERE(spacecraft EQ 'A', drcnt)
           IF (drcnt GT 0) THEN BEGIN
             msg= CHK_DR_OLAPS(cdoor(dr), odoor(dr), tel, 'A')
           ENDIF
         END
      2: BEGIN
           dr= WHERE(spacecraft EQ 'B', drcnt)
           IF (drcnt GT 0) THEN BEGIN
             msg= CHK_DR_OLAPS(cdoor(dr), odoor(dr), tel, 'B')
           ENDIF
         END
     ENDCASE
  ENDIF

  IF (msg(0) NE '') THEN BEGIN
    PRINT, msg
    WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
    POPUP_HELP, msg, TITLE= tel+' DOOR-CLOSURE CONFLICT'
    RETURN, msg
  ENDIF

  IF (msg1(0) NE '') THEN BEGIN
    PRINT, msg1
    WIDGET_CONTROL, mdiag, SET_VALUE= msg1(0)
    POPUP_HELP, msg1, TITLE= tel+' DOOR-CLOSURE CONFLICT'
    RETURN, msg1
  ENDIF

  RETURN, msg
END


FUNCTION CHK_DR_CONFS, os_arr, cdoor, odoor, tel, sc 

  msg= ''

     IF (tel EQ 'EUVI') THEN itel= 0
     IF (tel EQ 'COR1') THEN itel= 1
     IF (tel EQ 'COR2') THEN itel= 2
     ; pickup and check only non-calibration (not dark or led) images for this telescope, if any:
     tind= WHERE(os_arr.os_tele EQ itel AND os_arr.os_lp NE 2 AND os_arr.os_lp NE 3, tcnt)
     IF (tcnt GT 0) THEN BEGIN
       starts= os_arr(tind).os_start
       stops=  os_arr(tind).os_stop
       FOR i= 0, N_ELEMENTS(cdoor)-1 DO BEGIN
         cls= cdoor(i) -60 ; to allow for light travel-time offset, generate warning if image within 1min of door-close.
         opn= odoor(i) +60 ; to allow for light travel-time offset, generate warning if image within 1min of door-open. 
         ;oks= WHERE(stops LT cls OR starts GT opn, okcnt) 
         bads= WHERE(stops GE cls AND starts LE opn, badcnt)
         IF (badcnt GT 0) THEN BEGIN
           times= UTC2STR(TAI2UTC(cls),/TRUNCATE)+' and '+UTC2STR(TAI2UTC(opn),/TRUNCATE)
           img= tel+' Image'
           IF (badcnt GT 1) THEN img= img+'s'
           msg= 'FYI: Detected '+STRTRIM(badcnt,2)+' Non-Calibration '+img+ $
          ;      ' During '+times+' Door-Closure. Aborted Operation. Fix and Try Again.'
                ' During '+times+' Door-Closure (S/C '+sc+').'
           msg= [msg,'(Door-Closure period is extended by 1min on each side to account for light travel-time offset.)']
           RETURN, msg
         ENDIF
       ENDFOR 
     ENDIF
  RETURN, msg 
END



FUNCTION CHECK_DOOR_CONFLICTS, os_array, cdoors, odoors, tel, spacecraft, schedv_sc
COMMON DIALOG, mdiag,font

   msg= '' 
   IF (DATATYPE(os_array(0)) EQ 'STC' AND cdoors(0) GT 0) THEN BEGIN
     sc= spacecraft
     cdoor= cdoors
     odoor= odoors
     os_arr= os_array

     CASE schedv_sc OF
      0: BEGIN
           dr= WHERE(spacecraft EQ 'A', drcnt)
           os= WHERE(os_array.sc EQ 'A' OR os_arr.sc EQ 'AB', oscnt) 
           IF (drcnt GT 0 AND oscnt GT 0) THEN BEGIN
             msg= CHK_DR_CONFS(os_arr(os), cdoor(dr), odoor(dr), tel, 'A')
           ENDIF
           dr= WHERE(spacecraft EQ 'B', drcnt)
           os= WHERE(os_array.sc EQ 'B' OR os_arr.sc EQ 'AB', oscnt) 
           msg1= ''
           IF (drcnt GT 0 AND oscnt GT 0) THEN BEGIN
             msg1= CHK_DR_CONFS(os_arr(os), cdoor(dr), odoor(dr), tel, 'B')
           ENDIF
           msg= [msg,msg1]
         END
      1: BEGIN
           dr= WHERE(spacecraft EQ 'A', drcnt)
           os= WHERE(os_array.sc EQ 'A' OR os_arr.sc EQ 'AB', oscnt)
           IF (drcnt GT 0 AND oscnt GT 0) THEN BEGIN
             msg= CHK_DR_CONFS(os_arr(os), cdoor(dr), odoor(dr), tel, 'A')
           ENDIF 
         END
      2: BEGIN
           dr= WHERE(spacecraft EQ 'B', drcnt)
           os= WHERE(os_array.sc EQ 'B' OR os_arr.sc EQ 'AB', oscnt) 
           IF (drcnt GT 0 AND oscnt GT 0) THEN BEGIN
             msg= CHK_DR_CONFS(os_arr(os), cdoor(dr), odoor(dr), tel, 'B')
           ENDIF
         END
     ENDCASE
  ENDIF

  IF (msg(0) NE '') THEN BEGIN
    PRINT, msg
    WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
    POPUP_HELP, msg, TITLE= tel+' DOOR-CLOSURE CONFLICT'
  ENDIF

  RETURN, msg
END


PRO ADD_RS,OUT,trsc
 
  FOR i= 0, N_ELEMENTS(trsc)-1 DO BEGIN 
   stm= UTC2STR(TAI2UTC(trsc(i).dt),/ECS)
   PRINTF, OUT, 'PT_OS_NUM = 0004'
   PRINTF, OUT, 'PT_LP_NUM = 12'
   PRINTF, OUT, 'PT_LP_NSCHED = 1'
   gstart= 'PT_LP_START = ('+STRMID(stm,0,4)+STRMID(stm,5,2)+STRMID(stm,8,2)+'_'+ $
                            STRMID(stm,11,2)+STRMID(stm,14,2)+STRMID(stm,17,2)+')'
   gsc   = 'PT_LP_SC    = '+trsc(i).sc 
   PRINTF, OUT, gstart
   PRINTF, OUT, gsc
   PRINTF, OUT, 'PT_RSF= '+trsc(i).fn
   PRINTF, OUT, 'PT_BSF_CNT= '+STRTRIM(trsc(i).bsf,2)
   PRINTF, OUT, ';'
   PRINTF, OUT, ';'
  ENDFOR
  RETURN
END

PRO ADD_INIT,OUT,ics
  FOR i= 0, N_ELEMENTS(ics)-1 DO BEGIN
   stm= TAI2UTC(ics(i).dt,/ECS)
   PRINTF, OUT, 'PT_OS_NUM = 0003'
   PRINTF, OUT, 'PT_LP_NUM = 11'
   PRINTF, OUT, 'PT_LP_NSCHED = 1'
   gstart= 'PT_LP_START = ('+STRMID(stm,0,4)+STRMID(stm,5,2)+STRMID(stm,8,2)+'_'+ $
                             STRMID(stm,11,2)+STRMID(stm,14,2)+STRMID(stm,17,2)+')'
   gsc   = 'PT_LP_SC    = '+ics(i).sc
   PRINTF, OUT, gstart
   PRINTF, OUT, gsc
   PRINTF, OUT, 'PT_BSF_CNT= '+STRTRIM(ics(i).bsf,2)
   PRINTF, OUT, ';'
   PRINTF, OUT, ';'
  ENDFOR
  RETURN
END


PRO GENERATE_IPT, startdis, enddis, ipt_name, expand_bsf=expand_bsf, NO_EXPAND_BSF=no_expand_bsf

COMMON OP_SCHEDULED
COMMON OS_DEFINED
COMMON OS_SCHEDULED
COMMON DIALOG, mdiag,font
COMMON CMD_SEQ_SCHEDULED   ; AEE - 02/14/03

COMMON SCIP_DOORS_SHARE    ; AEE - 06/09/03 - add door close/open commands.
COMMON GT_DUMPS_SHARE      ; AEE - 07/25/03
COMMON APIDS, multi_apid   ; AEE - 07/25/03
COMMON LP_CAL_LAMP_SHARE, lpcalv ; AEE - 08/22/03
COMMON EXPANDED_OS,  expanded ; AEE 1/15/04
COMMON SCHED_SHARE, schedv
COMMON RUN_SCRIPT, rsc
COMMON INIT_TL, ic
COMMON TABLES_IN_USE, tables_used, tbAout,tbBout

    expand_bsf=1
    IF keyword_set(NO_EXPAND_BSF) THEN expand_bsf=0
    
   eucnt= 0
   IF (DATATYPE(sc_euvi) NE 'UND') THEN BEGIN
     IF (schedv.sc EQ 0) THEN eucnt= 1
     IF (schedv.sc EQ 1) THEN eua= WHERE(sc_euvi EQ 'A', eucnt)
     IF (schedv.sc EQ 2) THEN eub= WHERE(sc_euvi EQ 'B', eucnt)
   ENDIF
   c1cnt= 0
   IF (DATATYPE(sc_cor1) NE 'UND') THEN BEGIN
     IF (schedv.sc EQ 0) THEN c1cnt= 1
     IF (schedv.sc EQ 1) THEN c1a= WHERE(sc_cor1 EQ 'A', c1cnt)
     IF (schedv.sc EQ 2) THEN c1b= WHERE(sc_cor1 EQ 'B', c1cnt)
   ENDIF
   c2cnt= 0
   IF (DATATYPE(sc_cor2) NE 'UND') THEN BEGIN
     IF (schedv.sc EQ 0) THEN c2cnt= 1
     IF (schedv.sc EQ 1) THEN c2a= WHERE(sc_cor2 EQ 'A', c2cnt)
     IF (schedv.sc EQ 2) THEN c2b= WHERE(sc_cor2 EQ 'B', c2cnt)
   ENDIF
   gtcnt= 0
   IF (DATATYPE(sc_gt) NE 'UND') THEN BEGIN
     IF (schedv.sc EQ 0) THEN gtcnt= 1
     IF (schedv.sc EQ 1) THEN gta= WHERE(sc_gt EQ 'A' OR sc_gt EQ 'AB', gtcnt)
     IF (schedv.sc EQ 2) THEN gtb= WHERE(sc_gt EQ 'B' OR sc_gt EQ 'AB', gtcnt)
   ENDIF

   IF (DATATYPE(os_arr(0)) EQ 'INT' AND eucnt EQ 0 AND $
       N_ELEMENTS(ic) EQ 1 AND N_ELEMENTS(rsc) EQ 1 AND $ 
       c1cnt EQ 0 AND c2cnt EQ 0 AND gtcnt EQ 0) THEN BEGIN
      ipt_name= "Empty Schedule. Command Ignored."
      WIDGET_CONTROL,mdiag,SET_VALUE="%%GENERATE_IPT: "+ ipt_name
      PRINT, "%%GENERATE_IPT: "+ ipt_name
      RETURN
   ENDIF

   ;*************************************************
   ;** form IPT filename SECYYYYMMDDvvv.IPT
   ;**
   utc = TAI2UTC(startdis, /EXTERNAL)
   ipt_file_name = 'SEC'+STRN(utc.year)+STRN(utc.month,FORMAT='(I2.2)')+STRN(utc.day,FORMAT='(I2.2)')
 
   ;*************************************************
   ;** check for previous versions
   ;**
   ;f_exist = FINDFILE(GETENV('PT')+'/IO/IPT/'+ipt_file_name + '???.IPT', count=count)
   IF (schedv.sc EQ 0) THEN sc= 'SC_AB/'
   IF (schedv.sc EQ 1) THEN sc= 'SC_A/'
   IF (schedv.sc EQ 2) THEN sc= 'SC_B/'
   
   f_exist = FINDFILE(GETENV('PT')+'/IO/IPT/'+sc+ipt_file_name + '???.IPT', count=count)
   IF (f_exist(0) EQ '') THEN $                                   ;** first version
      ipt_file_name = ipt_file_name + '000.IPT' $
   ELSE BEGIN
      f_exist = STRUPCASE(f_exist(count-1))                         ;** make next version
      version = FIX(STRMID(f_exist,STRLEN(f_exist)-7,3))+1
      ipt_file_name = ipt_file_name + STRN(version,FORMAT='(I3.3)') + '.IPT'
   ENDELSE

   ipt_name = ipt_file_name

;   IF (DATATYPE(os_arr(0))  EQ 'INT' AND $
;       DATATYPE(cdoor_euvi) NE 'DOU' AND  DATATYPE(odoor_euvi) NE 'DOU' AND $
;       DATATYPE(cdoor_cor1) NE 'DOU' AND  DATATYPE(odoor_cor1) NE 'DOU' AND $
;       DATATYPE(cdoor_cor2) NE 'DOU' AND  DATATYPE(odoor_cor2) NE 'DOU' AND $
;       DATATYPE(stime_gt) NE 'DOU' AND DATATYPE(etime_gt) NE 'DOU') THEN RETURN ;AEE-7/25/03 add GT-dumps


   ; Check for EUVI, COR1, and COR2 "door overlaps" and "door vs non-calibration
   ; images" scheduling conflicts:

   IF (NOT KEYWORD_SET(expand_bsf)) THEN BEGIN
     IF (DATATYPE(cdoor_euvi) EQ 'DOU') THEN BEGIN
       IF (N_ELEMENTS(cdoor_euvi) GT 1) THEN BEGIN
         msg= CHECK_DOOR_OVERLAPS(cdoor_euvi,odoor_euvi,'EUVI',sc_euvi,schedv.sc) 
         IF (msg(0) NE '') THEN BEGIN
           ;PRINT, msg
           ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
           ;POPUP_HELP, msg, TITLE= 'EUVI DOOR-CLOSURE OVERLAPS'
           ipt_name= msg(0) 
           RETURN 
         ENDIF
       ENDIF
     ENDIF
     IF (DATATYPE(cdoor_cor1) EQ 'DOU') THEN BEGIN
       IF (N_ELEMENTS(cdoor_cor1) GT 1) THEN BEGIN
         msg= CHECK_DOOR_OVERLAPS(cdoor_cor1,odoor_cor1,'COR1',sc_cor1,schedv.sc) 
         IF (msg(0) NE '') THEN BEGIN
           ;PRINT, msg
           ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
           ;POPUP_HELP, msg, TITLE= 'COR1 DOOR-CLOSURE OVERLAPS'
           ipt_name= msg(0) 
           RETURN 
         ENDIF
       ENDIF
     ENDIF
     IF (DATATYPE(cdoor_cor2) EQ 'DOU') THEN BEGIN
       IF (N_ELEMENTS(cdoor_cor2) GT 1) THEN BEGIN
         msg= CHECK_DOOR_OVERLAPS(cdoor_cor2,odoor_cor2,'COR2',sc_cor2,schedv.sc) 
         IF (msg(0) NE '') THEN BEGIN
           ;PRINT, msg
           ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
           ;POPUP_HELP, msg, TITLE= 'COR2 DOOR-CLOSURE OVERLAPS'
           ipt_name= msg(0) 
           RETURN 
         ENDIF
       ENDIF
     ENDIF

     IF (DATATYPE(cdoor_euvi) EQ 'DOU') THEN BEGIN
       msg= CHECK_DOOR_CONFLICTS(os_arr,cdoor_euvi,odoor_euvi,'EUVI',sc_euvi,schedv.sc)
       IF (msg(0) NE '') THEN BEGIN
         ;PRINT, msg
         ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
         ;POPUP_HELP, msg, TITLE= 'EUVI DOOR-CLOSURE CONFLICT'
         ;ipt_name= msg(0) 
         ;RETURN 
       ENDIF
     ENDIF

     IF (DATATYPE(cdoor_cor1) EQ 'DOU') THEN BEGIN
       msg= CHECK_DOOR_CONFLICTS(os_arr,cdoor_cor1,odoor_cor1,'COR1',sc_cor1,schedv.sc)
       IF (msg(0) NE '') THEN BEGIN
         ;PRINT, msg
         ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
         ;POPUP_HELP, msg, TITLE= 'COR1 DOOR-CLOSURE CONFLICT'
         ;ipt_name= msg(0)
         ;RETURN
       ENDIF
     ENDIF
     IF (DATATYPE(cdoor_cor2) EQ 'DOU') THEN BEGIN
       msg= CHECK_DOOR_CONFLICTS(os_arr,cdoor_cor2,odoor_cor2,'COR2',sc_cor2,schedv.sc)
       IF (msg(0) NE '') THEN BEGIN
         ;PRINT, msg
         ;WIDGET_CONTROL, mdiag, SET_VALUE= msg(0)
         ;POPUP_HELP, msg, TITLE= 'COR2 DOOR-CLOSURE CONFLICT'
         ;ipt_name= msg(0)
         ;RETURN
       ENDIF
     ENDIF

   ENDIF

   OPENW, OUT, GETENV('PT')+'/IO/IPT/'+sc+ipt_file_name, /GET_LUN
   WIDGET_CONTROL,mdiag,SET_VALUE='%%%GENERATE_IPT: Creating file: '+ ipt_file_name
   PRINT,'%%%GENERATE_IPT: Creating file: '+ ipt_file_name
   WIDGET_CONTROL, /HOUR

   IF (schedv.sc EQ 0) THEN tables= [tbAout,tbBout] 
   IF (schedv.sc EQ 1) THEN tables= tbAout
   IF (schedv.sc EQ 2) THEN tables= tbBout
   tables= [';PT Schedule = '+sc+ipt_file_name,tables]
   FOR tb= 0, N_ELEMENTS(tables)-1 DO PRINTF, OUT, tables(tb)

   ; Add I (Initialize timeline) command to the IPT schedule file if not marked as
   ; one that belongs to a .bsf file.  If creating a .bsf file, then I command, if any, 
   ; should also be added to .BSF files so don't check for expand_bsf keyword:

   tic= ic
   IF (NOT KEYWORD_SET(expand_bsf)) THEN BEGIN
     tind= WHERE(ic.bsf LT 1, tcnt)  ; pickup commands not belonging to .bsf, if any
     IF (tcnt GT 0) THEN tic= tic(tind) 
   ENDIF
   IF (N_ELEMENTS(tic) GT 1) THEN BEGIN
     CASE schedv.sc OF
       0: BEGIN 
            ADD_INIT, OUT, tic(1:N_ELEMENTS(tic)-1)
          END
       1: BEGIN
            aic= WHERE(tic.sc EQ 'A', acnt)
            IF (acnt GT 0) THEN ADD_INIT, OUT, tic(aic) 
          END
       2: BEGIN
            bic= WHERE(tic.sc EQ 'B', bcnt)
            IF (bcnt GT 0) THEN ADD_INIT, OUT, tic(bic)
          END
     ENDCASE 
   ENDIF

  ; Now do the same for A (Run Script) commands:

   tic= rsc
   IF (NOT KEYWORD_SET(expand_bsf)) THEN BEGIN
     tind= WHERE(rsc.bsf LT 1, tcnt)  ; pickup commands not belonging to .bsf, if any
     IF (tcnt GT 0) THEN tic= tic(tind)
   ENDIF
   IF (N_ELEMENTS(tic) GT 1) THEN BEGIN
     CASE schedv.sc OF
       0: BEGIN
            ADD_RS, OUT, tic(1:N_ELEMENTS(tic)-1)
          END
       1: BEGIN
            aic= WHERE(tic.sc EQ 'A', acnt)
            IF (acnt GT 0) THEN ADD_RS, OUT, tic(aic)
          END
       2: BEGIN
            bic= WHERE(tic.sc EQ 'B', bcnt)
            IF (bcnt GT 0) THEN ADD_RS, OUT, tic(bic)
          END
     ENDCASE
   ENDIF


   ; AEE - 06/09/03 Add SCIP door commands to the IPT schedule file:
  
   IF (NOT KEYWORD_SET(expand_bsf)) THEN BEGIN
     ADD_DOOR_CMND,OUT,cdoor_euvi,0,8,sc_euvi,schedv.sc   ; close-doors for EUVI (tel=0, lp=8)
     ADD_DOOR_CMND,OUT,odoor_euvi,0,9,sc_euvi,schedv.sc   ;  open-doors for EUVI (tel=0, lp=9)
     ADD_DOOR_CMND,OUT,cdoor_cor1,1,8,sc_cor1,schedv.sc   ; close-doors for COR1 (tel=1, lp=8)
     ADD_DOOR_CMND,OUT,odoor_cor1,1,9,sc_cor1,schedv.sc   ;  open-doors for COR1 (tel=1, lp=9)
     ADD_DOOR_CMND,OUT,cdoor_cor2,2,8,sc_cor2,schedv.sc   ; close-doors for COR2 (tel=2, lp=8)
     ADD_DOOR_CMND,OUT,odoor_cor2,2,9,sc_cor2,schedv.sc   ;  open-doors for COR2 (tel=2, lp=9)
   ENDIF

   ; AEE - 07/25/03 Add GuideTelescope dump commands to the IPT schedule file:

   ;IF (DATATYPE(apid_gt) NE 'UND') THEN BEGIN
   ;IF (DATATYPE(apid_gt) NE 'UND' AND (NOT KEYWORD_SET(expand_bsf))) THEN BEGIN
   ;IF (DATATYPE(apid_gt) NE 'UND' AND DATATYPE(sc_gt) NE 'UND' AND $
   ;    (NOT KEYWORD_SET(expand_bsf))) THEN BEGIN

   ; Allow GT-dumps for BSF files:
   ; Only add GT-dumps to IPT file that don't belong to a bsf file (unless expand_bsf keyword is set):
   IF (DATATYPE(apid_gt) NE 'UND' AND DATATYPE(sc_gt) NE 'UND') THEN BEGIN
     IF (schedv.sc EQ 0) THEN BEGIN 
       ;ADD_GT_CMND,OUT,stime_gt,etime_gt,apid_gt,sc_gt,10   ; assign LP=10 to GT dumps.
       IF (KEYWORD_SET(expand_bsf)) THEN BEGIN
         ADD_GT_CMND,OUT,stime_gt,etime_gt,apid_gt,sc_gt,10,rate_gt
       ENDIF ELSE BEGIN
         ;ok= WHERE(bsf_gt EQ '',no_bsf)
         ;ADD_GT_CMND,OUT,stime_gt(ok),etime_gt(ok),apid_gt(ok),sc_gt(ok),10,rate_gt(ok) 
         ok= WHERE(bsf_gt EQ '' OR sc_gt EQ 'AB',no_bsf)
         IF (no_bsf GT 0) THEN BEGIN 
           tsc_gt= sc_gt(ok)
           tbsf_gt= bsf_gt(ok)
           FOR b=0, no_bsf-1 DO BEGIN
             IF (tbsf_gt(b) NE '') THEN BEGIN
               tsc_gt(b)= 'A'
               IF (STRMID(tbsf_gt(b),0,1) EQ 'A') THEN tsc_gt(b)= 'B' 
             ENDIF
           ENDFOR
           ADD_GT_CMND,OUT,stime_gt(ok),etime_gt(ok),apid_gt(ok),tsc_gt,10,rate_gt(ok) 
         ENDIF
       ENDELSE
     ENDIF
     wcnt= 0
     IF (KEYWORD_SET(expand_bsf)) THEN BEGIN
       IF (schedv.sc EQ 1) THEN w= WHERE(sc_gt EQ 'A' OR sc_gt EQ 'AB', wcnt)
       IF (schedv.sc EQ 2) THEN w= WHERE(sc_gt EQ 'B' OR sc_gt EQ 'AB', wcnt) 
     ENDIF ELSE BEGIN
       IF (schedv.sc EQ 1) THEN w= WHERE((sc_gt EQ 'A' OR sc_gt EQ 'AB') AND $
                                         (bsf_gt EQ '' OR STRMID(bsf_gt,0,1) EQ 'B'), wcnt)
       IF (schedv.sc EQ 2) THEN w= WHERE((sc_gt EQ 'B' OR sc_gt EQ 'AB') AND $
                                         (bsf_gt EQ '' OR STRMID(bsf_gt,0,1) EQ 'A'), wcnt) 
     ENDELSE  
     IF (wcnt GT 0) THEN $
       ADD_GT_CMND,OUT,stime_gt(w),etime_gt(w),apid_gt(w),sc_gt(w),10,rate_gt(w)
   ENDIF

   IF (DATATYPE(os_arr(0)) EQ 'INT') THEN BEGIN ; only door commands and/or GT dumps in ipt file (no OSes)
     CLOSE, OUT
     FREE_LUN, OUT
     WIDGET_CONTROL,mdiag,SET_VALUE='%%%GENERATE_IPT: (../IO/IPT/'+sc+ipt_file_name+') Done.'
     PRINT,'%%%GENERATE_IPT: (../IO/IPT/'+sc+ipt_file_name+') Done.'
     RETURN 
   END


   ; AEE - 02/14/03; Separate Block Sequences from rest of the OSes (temporarily just for 
   ;                 generating the IPT file so that if generating an IPT file is not the
   ;                 last thing that operator does, the block sequences are not lost in os_arr):

   ;  *** Must add this code to rest of the files that generate output ***

   temp_os_arr= os_arr ; AEE 5/22/03 - os_arr, if changed, will be restored before each RETURN and at
                       ; the end of this routine.

   ;IF (DATATYPE(sched_cmdseq) EQ 'STC') THEN BEGIN
   IF (DATATYPE(sched_cmdseq) EQ 'STC' AND (NOT KEYWORD_SET(expand_bsf)) ) THEN BEGIN
     FOR bsf_sc= 1,2 DO BEGIN
       IF (bsf_sc EQ 1) THEN sct= WHERE(sched_cmdseq.sc EQ 'A',sc_cnt) 
       IF (bsf_sc EQ 2) THEN sct= WHERE(sched_cmdseq.sc EQ 'B',sc_cnt)
       IF (sc_cnt GT 0) THEN BEGIN
         tsched_cmdseq= sched_cmdseq(sct)
         cmd_seq_num= N_ELEMENTS(tsched_cmdseq) 
         FOR i= 0, cmd_seq_num-1 DO BEGIN
           sched_os = os_arr.os_num  
           sched_time = UTC2STR(TAI2UTC(os_arr.os_start),/ECS)
           sched_sc = os_arr.sc
           cmdseq_os= LONG(STR_SEP(tsched_cmdseq(i).os_num,','))
           cmdseq_time= STR_SEP(tsched_cmdseq(i).os_time,',')
           cmdseq_sc= tsched_cmdseq(i).sc
           ; A cmdseq may have more than one entry (more than one OS_NUM) in it, so
           ; write to .IPT file one once, but loop through all OS_NUMs in the cmdseq
           ; to remove them from os_arr:

           FOR j=0, N_ELEMENTS(cmdseq_os)-1 DO BEGIN
             IF (j EQ 0) THEN BEGIN
               PRINTF, OUT, 'PT_OS_NUM = 0000'
               PRINTF, OUT, 'PT_LP_NUM = 7'
               PRINTF, OUT, 'PT_BSFILE = '+STRTRIM(tsched_cmdseq(i).bsfile,2)
               start= tsched_cmdseq(i).start_time
               PRINTF, OUT, 'PT_LP_START = ('+STRMID(start,0,4)+STRMID(start,5,2)+STRMID(start,8,2)+'_'+ $
                                              STRMID(start,11,2)+STRMID(start,14,2)+STRMID(start,17,2)+')'
               PRINTF, OUT, 'PT_LP_SC= '+tsched_cmdseq(i).sc
               PRINTF, OUT, ';'
               PRINTF, OUT, ';' 
             ENDIF
             ; select OS(es) that do not belong to the cmdseq and keep them in os_arr:
             w1= WHERE(sched_os NE cmdseq_os(j) OR sched_time NE cmdseq_time(j) OR $
                       sched_sc NE cmdseq_sc, w1cnt)
             IF (w1cnt GT 0) THEN BEGIN 
               sched_os = sched_os(w1)
               sched_time = sched_time(w1)
               sched_sc = sched_sc(w1)
               os_arr= os_arr(w1)
             ENDIF ELSE BEGIN  ; all scheduled OSes were Command Sequences.
              ; if no OSes remain but there are still bsf files to be processed that don't have images, 
              ; mark the os_arr as empty (set os_num= -1):
              IF (N_ELEMENTS(os_arr) EQ 1) THEN os_arr(0).os_num= -1

              IF (i EQ cmd_seq_num-1) THEN BEGIN
               CLOSE, OUT
               FREE_LUN, OUT
               WIDGET_CONTROL,mdiag,SET_VALUE='%%%GENERATE_IPT: (../IO/IPT/'+sc+ipt_file_name+') Done.'
               PRINT,'%%%GENERATE_IPT: (../IO/IPT/'+sc+ipt_file_name+') Done.'
               os_arr= temp_os_arr ;AEE 5/22/03 restore os_arr to its original
               RETURN
              ENDIF
             ENDELSE
           ENDFOR
         ENDFOR
       ENDIF
     ENDFOR 
   ENDIF

   os_arr2 = os_arr(SORT([os_arr.os_num]))   ;** sort on os_num
   uniq_os_arr2 = os_arr2(UNIQ([os_arr2.os_num]))
   num_os = N_ELEMENTS(uniq_os_arr2)

  ; If os_num was set to -1, ignore rest of this code and just close the file (set num_os= -1:
  IF (os_arr(0).os_num eq -1) THEN num_os= -1

   FOR i = num_os-1, 0, -1 DO BEGIN    ;** for every unique os_num

      os_num = uniq_os_arr2(i).os_num
      PRINTF, OUT, 'PT_OS_NUM = '+STRING(os_num,FORMAT='(I4.4)')
      ;PRINTF, OUT, 'PT_SET_ID = 0000' ; AEE 2/12/04 - Added.
      ;PRINTF, OUT, 'PT_SET_ID = '+STRING(uniq_os_arr2(i).set_id,FORMAT='(I4.4)')

      index = WHERE(defined_os_arr.os_num EQ os_num AND $
                    defined_os_arr.num_images GT 0, oscnt)    ; AEE - 01/10/03 

    FOR cnt= 0, oscnt-1 DO BEGIN  ; AEE - Dec 05, 02 ; if os_cnt=2 => lp=6 (HI Seq)
      ind= index(cnt)
      lp = defined_os_arr(ind).lp

      ; Identify second OS of LP=6 (when both HI1 and 2 are used with minus os_num):

      IF (cnt EQ 1) THEN PRINTF, OUT, 'PT_OS_NUM = -'+STRING(os_num,FORMAT='(I4.4)') 
      PRINTF, OUT, 'PT_LP_NUM = ' + STRTRIM(lp,2)

      PRINTF, OUT, 'PT_LP_EXIT = '+STRTRIM(0,2)	;** for now always use exit by iteration
      iter_cnt = 1				;** for now always schedule just 1
      PRINTF, OUT, 'PT_LP_ITER = '+STRTRIM(iter_cnt,2)

      ; AEE - Dec 31, 02 - separate HI1 and HI2 (in HI Seq) nsched:
      good = WHERE(os_arr.os_num EQ uniq_os_arr2(i).os_num AND os_arr.os_tele EQ defined_os_arr(ind).tele)

      ;** sort on start time
      nsched = N_ELEMENTS(good)
      IF (nsched GT 1) THEN good = good(SORT([os_arr(good).os_start]))
      first_os = os_arr(good(0))
      PRINTF, OUT, 'PT_LP_NSCHED = '+STRTRIM(nsched,2)

      ; pickup SpaceCraft ID(s):
      sc_id= '('
      FOR sc_cnt=0, nsched -2 DO BEGIN
        sc_id= sc_id + os_arr(good(sc_cnt)).sc
        ;IF (schedv.sc EQ 0) THEN sc_id= sc_id + os_arr(good(sc_cnt)).sc
        ;IF (schedv.sc EQ 1) THEN sc_id= sc_id + 'A'
        ;IF (schedv.sc EQ 2) THEN sc_id= sc_id + 'B'
        sc_id= sc_id  + ','
      ENDFOR 
      IF (nsched GT 1) THEN BEGIN 
        sc_id= sc_id + os_arr(good(sc_cnt)).sc
        ;IF (schedv.sc EQ 0) THEN sc_id= sc_id + os_arr(good(sc_cnt)).sc 
        ;IF (schedv.sc EQ 1) THEN sc_id= sc_id + 'A'
        ;IF (schedv.sc EQ 2) THEN sc_id= sc_id + 'B'
      ENDIF ELSE BEGIN 
        sc_id= sc_id + os_arr(good(0)).sc
        ;IF (schedv.sc EQ 0) THEN sc_id= sc_id + os_arr(good(0)).sc
        ;IF (schedv.sc EQ 1) THEN sc_id= sc_id + 'A'
        ;IF (schedv.sc EQ 2) THEN sc_id= sc_id + 'B'
      ENDELSE
      sc_id= sc_id + ')'
      PRINTF, OUT, 'PT_SC_ID = '+sc_id
      PRINTF, OUT, 'PT_SET_ID = ('+ARR2STR(os_arr(good).set_id,/TRIM)+')'


      ; pick up img_cntr for images. For a seq of N images, all N images have the same img_cntr and 
      ; seq_cntr of 1-N but for a summed-seq, only the Nth imags exists with seq_cntr set to N: 

      eind= WHERE(expanded.os_num EQ os_num AND expanded.os_start EQ os_arr(good(0)).os_start)
      FOR osind= 1, nsched-1 DO BEGIN
        eind= [eind,WHERE(expanded.os_num EQ os_num AND expanded.os_start EQ os_arr(good(osind)).os_start)]
      ENDFOR

      expand= expanded(eind)

      img_cnt= expand.img_cnt ;two non-seq images may have the same img_cnt when schedule expands beyond 1 day

      ;img_cnt= expand(UNIQ_NOSORT(expand.img_cnt)).img_cnt  ; for all LPs 

      ; since at start of each days, img_cnt is set to 1, breakup schedule to daily pieces (if expands
      ; into next day(s)) so that same cntrs (starting with 1 again) are not lost when using uniq:

        sdays= long(expand.start / 24.0)
        unq_sdays= UNIQ_NOSORT(sdays)
        unq_sdays= [unq_sdays,N_ELEMENTS(sdays)-1] ; now have index range for each day
        img_cnt= -1 
        FOR ud= 0, N_ELEMENTS(unq_sdays)-2 DO BEGIN
          ;daily_cnt= expand(unq_sdays(ud):unq_sdays(ud+1)-1).img_cnt
          daily_cnt= expand(unq_sdays(ud):unq_sdays(ud+1)).img_cnt
         img_cnt= [img_cnt,daily_cnt(UNIQ_NOSORT(daily_cnt))] 
        ENDFOR
        img_cnt= img_cnt(1:*)

      img_cntr= '('+STRTRIM(img_cnt(0),2)
      FOR ucnt= 1, N_ELEMENTS(img_cnt)-1 DO $
        img_cntr= img_cntr + ','+STRTRIM(img_cnt(ucnt),2)
      img_cntr= img_cntr + ')'
      PRINTF, OUT, 'PT_IMG_CNTR= '+STRTRIM(img_cntr,2)

      seq_cnt=expand(UNIQ_NOSORT(expand.seq_cnt)).seq_cnt

      seq_cntr= '('+STRTRIM(seq_cnt(0),2)
      FOR ucnt= 1, N_ELEMENTS(seq_cnt)-1 DO $
        seq_cntr= seq_cntr + ','+STRTRIM(seq_cnt(ucnt),2)
      seq_cntr=  seq_cntr + ')'
      PRINTF, OUT, 'PT_SEQ_CNTR= '+STRTRIM(seq_cntr,2)

;      sfn= expand.sfn
;      sfns= '('+STRTRIM(sfn(0),2)
;      FOR ucnt= 1, N_ELEMENTS(sfn)-1  DO sfns= sfns+ ','+STRTRIM(sfn(ucnt),2)
;      sfns=  sfns + ')'
;      PRINTF, OUT, 'PT_SFN= '+STRTRIM(sfns,2)


      ;** output start times
      c = 0 					;** counter, only 5 start times per line
      cc = 0 					;** counter, only 5 start times per line
      ccc = 0 					;** counter, only 5 start times per line
      c4 = 0 					;** counter, only 5 start times per line
      FOR j=0, nsched-1 DO BEGIN 		;** for every occurance of this os_num
         IF (c EQ 0) THEN str = '('		;** new line
         IF (cc EQ 0) THEN cam_str = '('		;** new line
         os_start = os_arr(good(j)).os_start
         utc = TAI2UTC(os_start, /EXTERNAL)
         yy = STRTRIM(utc.year,2) 
         mm = STRTRIM(utc.month,2) & IF (STRLEN(mm) EQ 1) THEN mm = '0'+mm
         dd = STRTRIM(utc.day,2)   & IF (STRLEN(dd) EQ 1) THEN dd = '0'+dd
         hh = STRTRIM(utc.hour,2)  & IF (STRLEN(hh) EQ 1) THEN hh = '0'+hh
         mi = STRTRIM(utc.minute,2)& IF (STRLEN(mi) EQ 1) THEN mi = '0'+mi
         ss = STRTRIM(utc.second,2)& IF (STRLEN(ss) EQ 1) THEN ss = '0'+ss
         tt = yy+mm+dd+'_'+hh+mi+ss
         str = str + tt + ','
         IF (DATATYPE(load_camtable) EQ 'STC') THEN BEGIN
            cind = WHERE((os_num EQ load_camtable.os_num) AND (os_start EQ load_camtable.os_start))
            IF (cind(0) NE -1) THEN BEGIN
               cam_str = cam_str + tt + ','
               cc = cc + 1
            ENDIF
         ENDIF
         c = c + 1
         IF ((c EQ 5) OR (j EQ (nsched-1))) THEN BEGIN	;** only 5 entries per line
            str = STRMID(str,0,STRLEN(str)-1) + ')'
            PRINTF, OUT, 'PT_LP_START = '+str
            c = 0
         ENDIF
      ENDFOR					;** for every start time for this os_num

      cam_str = STRMID(cam_str,0,STRLEN(cam_str)-1) + ')'
      IF (cam_str NE ')') THEN PRINTF, OUT, 'PT_LOAD_CAM = '+cam_str

      tele = defined_os_arr(ind).tele
      fw = defined_os_arr(ind).fw
      pw = defined_os_arr(ind).pw
      sub = defined_os_arr(ind).sub
      start = defined_os_arr(ind).start
      exptable = defined_os_arr(ind).exptable  ; AEE 1/14/04
      camtable = defined_os_arr(ind).camtable  ; AEE 1/14/04
      fps = defined_os_arr(ind).fps ; AEE 1/14/04
      iptable = defined_os_arr(ind).iptable
      lamp = defined_os_arr(ind).lamp
      num_images = defined_os_arr(ind).num_images
      ccd = defined_os_arr(ind).ccd
      ip = defined_os_arr(ind).ip
      ex = defined_os_arr(ind).ex
      occ_blks = REFORM(defined_os_arr(ind).occ_blocks(tele,*))
      roi_blks = REFORM(defined_os_arr(ind).roi_blocks(tele,*))

      IF (lp EQ 7) THEN BEGIN ;** Block Seq   AEE 5/20/03 
         PRINTF, OUT, 'PT_START = '+STRTRIM(start,2)
         PRINTF, OUT, 'PT_STOP = '+STRTRIM(num_images,2)
         GOTO, CONT
      ENDIF

      PRINTF, OUT, 'PT_TELE = '+STRTRIM(tele,2)
      ;PRINTF, OUT, 'PT_DPT = '+STRTRIM(table+1,2)	;** cnvrt: LEB wants 1-3   ; AEE 1/14/04
      PRINTF, OUT, 'PT_EXPT = '+STRTRIM(exptable+1,2)  ; AEE 1/14/04
      PRINTF, OUT, 'PT_CAMT = '+STRTRIM(camtable+1,2)  ; AEE 1/14/04
      PRINTF, OUT, 'PT_FW = '+STRTRIM(fw,2)

      IF (lp EQ 200) THEN BEGIN	; AEE -8/23/03
      ENDIF ELSE BEGIN			;** output pw/exp pairs
         pwstr = '('
         expstr = '('

         ; For non cal images, report exptime that is corrected for CCD summing:

         ccdsum= 1
         IF (lp NE 2 AND lp NE 3) THEN BEGIN
           xs = ccd(tele,camtable).xsum
           ys = ccd(tele,camtable).ysum
           ccdsum= ((xs > 1) * (ys > 1))
           IF (ccd(tele,camtable).gmode EQ 1) THEN ccdsum= ccdsum/4.0 ; for low gain, amplify exptime by 4
         ENDIF

        ccdsum=1 ; ignore ccd_sum and low gain exptime correction.

         FOR n=0, num_images -1 DO BEGIN  ;** for each pw position in the seq (for non-seq num_images=1 always)
            IF (tele GE 3) THEN BEGIN ; AEE March 19, 2003
              ; Note: HI telescpes do not have a shtter, polarizer, or filter wheels so pw(0) is only used.
              pwstr = pwstr + STRTRIM(pw(0),2) + ','
              IF (lp EQ 4) THEN BEGIN 
                expstr = expstr + STRTRIM(0,2) + ','   ; AEE 5/22/03
              ENDIF ELSE BEGIN 
                expstr = expstr + STRTRIM(STRING(ex(tele,exptable,fw,pw(0))/ccdsum,FORMAT='(I7)'),2) + ','
              ENDELSE
              IF (lp EQ 0) THEN BEGIN
                ; For double sky images, add the second pw and exp.time (for these images n is always 0)
                ; and since it is a HI image, the second pw and, therefore, exp.time are the same as the first.
                pwstr = pwstr + STRTRIM(pw(0),2) + ','
                expstr = expstr + STRTRIM(STRING(ex(tele,exptable,fw,pw(0))/ccdsum,FORMAT='(I7)'),2) + ','
              ENDIF
            ENDIF ELSE BEGIN
              pwstr = pwstr + STRTRIM(pw(n),2) + ','
              IF (lp EQ 4) THEN BEGIN 
                expstr = expstr + STRTRIM(0,2) + ','   ; AEE 5/22/03
              ENDIF ELSE BEGIN
                expstr = expstr + STRTRIM(STRING(ex(tele,exptable,fw,pw(n))/ccdsum,FORMAT='(I7)'),2) + ','
              ENDELSE
              IF (lp EQ 0) THEN BEGIN
                ; For double sky images, add the second pw and exp.time (for these images n is always 0)
                ; and pw(1) indicates the second pw positions and exptime to be used. 
                pwstr = pwstr + STRTRIM(pw(1),2) + ','
                expstr = expstr + STRTRIM(STRING(ex(tele,exptable,fw,pw(1))/ccdsum,FORMAT='(I7)'),2) + ',' 
              ENDIF
            ENDELSE

         ENDFOR

         pwstr = STRMID(pwstr,0,STRLEN(pwstr)-1) + ')'
         PRINTF, OUT, 'PT_PW = '+pwstr
         expstr = STRMID(expstr,0,STRLEN(expstr)-1) + ')'
         PRINTF, OUT, 'PT_EXPTIME = '+expstr
      ENDELSE
      IF (lamp GT 2) then BEGIN ; AEE - 8/22/03
        WIDGET_CONTROL,mdiag,SET_VALUE='%%%GENERATE_IPT:  STOP -  PT_CAL_LAMP = '+STRING(lamp,'(I3)')+ $
                                       ', from input, is out of range.' 
        PRINT,''
        PRINT,'STOP -  PT_CAL_LAMP = '+STRING(lamp,'(I3)')+', from input, is out of range.'
        PRINT,'        Exit the program, fix the problem, and start again.'
        PRINT,''
        STOP 
      ENDIF

      PRINTF, OUT, 'PT_CAL_LAMP = '+STRTRIM(lamp,2)
      str = '('+STRTRIM(ccd(tele,camtable).y1,2)+','
      str = str+STRTRIM(ccd(tele,camtable).x1,2)+','
      str = str+STRTRIM(ccd(tele,camtable).y2,2)+','
      str = str+STRTRIM(ccd(tele,camtable).x2,2)+','
      str = str+STRTRIM(ccd(tele,camtable).ysum,2)+','
      str = str+STRTRIM(ccd(tele,camtable).xsum,2)+')'
      PRINTF, OUT, 'PT_CAM_RO = '+str
      str = '('+STRTRIM(ccd(tele,camtable).pform,2)+',' 
      str = str+STRTRIM(FIX(ccd(tele,camtable).clr_id),2)+','
      str = str+STRTRIM(ccd(tele,camtable).rdout_id,2)+','
      str = str+STRTRIM(ccd(tele,camtable).cl_time,2)+','
      str = str+STRTRIM(ccd(tele,camtable).ro_time,2)+')'

      PRINTF, OUT, 'PT_CAM_OTH = '+str

      ;** print out the image processing table number 
      PRINTF, OUT, 'PT_IP_TAB_NUM = '+STRTRIM(iptable,2)

      good = WHERE(ip(iptable).steps GE 0, nip)
      str = '('
      FOR n=0, nip-1 DO BEGIN
         str = str+STRTRIM(ip(iptable).steps(good(n)),2)+','
      ENDFOR
      PRINTF, OUT, 'PT_NIP = '+STRTRIM(nip,2)
      str = STRMID(str,0,STRLEN(str)-1) + ')'
      PRINTF, OUT, 'PT_IP = '+str

      ; AEE 5/5/04:
      ind = WHERE(ip(iptable).steps EQ 28) ; 28 = don't use occ mask table. 
      IF (ind(0) GE 0) THEN useocc = 0 ELSE useocc = 1  ; Also see os_get_num_pixels.pro
                                                        ;          generate_ipt.pro
                                                        ;          generate_ipt_set.pro
                                                        ;          os_summary.pro
                                                        ;          os_summary_1line.pro
                                                        ;          os_summary_set.pro
                                                        ;          os_summary_text.pro
 
      ;ind = WHERE(ip(iptable).steps EQ 25)
      ;IF (ind(0) LT 0) THEN useroi = 0 ELSE useroi = 1

      roi_table= WHICH_ROI_TABLE(ip,iptable)
      IF (roi_table EQ -1) THEN useroi = 0 ELSE useroi = 1

         RESTORE,GETENV('PT')+'/IN/OTHER/ccd_size.sav'

         IF (useocc EQ 1) THEN BEGIN		;** Occulter Mask
            blocks = occ_blks
            p1 = 'PT_NOCC = '
            p2 = 'PT_OCC_MASK = '
            good = WHERE(blocks GE 1, nb)
            PRINTF, OUT, p1+STRTRIM(nb,2)
            chng_arr= INTARR(xyblks*xyblks)
            IF (nb GT 0) THEN BEGIN 
              ;change= MODIFY_MASK_ORDER(good) ; AEE 5/26/04 - change order from idl to mask_table.
              telid= ['EUVI','COR1','COR2','HI1','HI2']
              telstr= telid(tele)
              scid=['A','A','B'] ; first 'A' is really 'AB' but can't have it for mask.
              scstr= scid(schedv.sc)
              change= MODIFY_MASK_ORDER(scstr,telstr,good) ; change order from idl to mask_table.
              chng_arr(change)= 1
            ENDIF
            runs = FIND_DATA_RUNS(INDGEN(xyblks*xyblks),chng_arr,0,0,1)

            c = 0 	;** counter, only 5 entries per line
            pairs = (N_ELEMENTS(runs)/2)
            FOR p=0, pairs-1 DO BEGIN
               IF (c EQ 0) THEN str = '('				;** new line
               IF (runs(p,0) EQ runs(p,1)) THEN $			;** ex. use 39, instead of 39-39,
                  str = str + STRTRIM(runs(p,0),2) + ',' $
               ELSE $
                  str = str + STRTRIM(runs(p,0),2) + '-' + STRTRIM(runs(p,1),2) + ','
               c = c + 1
               IF ((c EQ 5) OR (p EQ (pairs-1))) THEN BEGIN	;** only 5 entries per line
                  str = STRMID(str,0,STRLEN(str)-1) + ')'
                  PRINTF, OUT, p2+str
                  c = 0
               ENDIF
            ENDFOR		;** for each pair
         ENDIF
         IF (useroi EQ 1) THEN BEGIN		;** ROI Mask
            blocks = roi_blks
            p1 = 'PT_NROI = '
            p2 = 'PT_ROI_MASK = '
            good = WHERE(blocks GE 1, nb)
            PRINTF, OUT, p1+STRTRIM(nb,2)
            chng_arr= INTARR(xyblks*xyblks)
            IF (nb GT 0) THEN BEGIN 
              ;change= MODIFY_MASK_ORDER(good) ; AEE 5/26/04 - change order from idl to mask_table.
              telid= ['EUVI','COR1','COR2','HI1','HI2']
              telstr= telid(tele)
              scid=['A','A','B'] ; first 'A' is really 'AB' but can't have it for mask.
              scstr= scid(schedv.sc)
              change= MODIFY_MASK_ORDER(scstr,telstr,good) ; change order from idl to mask_table.
              chng_arr(change)= 1
            ENDIF
            runs = FIND_DATA_RUNS(INDGEN(xyblks*xyblks),chng_arr,0,0,1)
            c = 0 	;** counter, only 5 entries per line
            pairs = (N_ELEMENTS(runs)/2)
            FOR p=0, pairs-1 DO BEGIN
               IF (c EQ 0) THEN str = '('				;** new line
               IF (runs(p,0) EQ runs(p,1)) THEN $			;** ex. use 39, instead of 39-39,
                  str = str + STRTRIM(runs(p,0),2) + ',' $
               ELSE $
                  str = str + STRTRIM(runs(p,0),2) + '-' + STRTRIM(runs(p,1),2) + ','
               c = c + 1
               IF ((c EQ 5) OR (p EQ (pairs-1))) THEN BEGIN	;** only 5 entries per line
                  str = STRMID(str,0,STRLEN(str)-1) + ')'
                  PRINTF, OUT, p2+str
                  c = 0
               ENDIF
            ENDFOR		;** for each pair
         ENDIF

CONT:

      ;os_size = first_os.os_size
      os_size = LONG(first_os.os_size / 8.0) ; change to bytes
      os_duration = first_os.os_duration
      aind= WHERE(multi_apid.os_num EQ os_num)  ; AEE - 7/25/03
      PRINTF, OUT, 'PT_OS_SIZE = '+STRTRIM(os_size,2)
      PRINTF, OUT, 'PT_OS_DUR = '+STRTRIM(STRING(os_duration,'(f20.2)'),2)
      PRINTF, OUT, 'PT_OS_PROCT = '+STRTRIM(STRING(first_os.os_proc_time,'(f20.2)'),2)
      PRINTF, OUT, 'PT_OS_ROT = '+STRTRIM(STRING(first_os.os_ro_time,'(f20.2)'),2)  ; AEE - 01/28/03
      PRINTF, OUT, 'PT_OS_PPT = '+STRTRIM(STRING(first_os.os_pre_proc_time,'(f20.2)'),2)  ; AEE - 01/28/03
      PRINTF, OUT, 'PT_OS_SETUP = '+STRTRIM(STRING(first_os.os_setup_time,'(f20.2)'),2)
      PRINTF, OUT, 'PT_OS_CAD = '+STRTRIM(STRING(first_os.os_cadence,'(f20.2)'),2)  ; AEE - 01/28/03

      ;PRINTF, OUT, 'PT_OS_SIZES= '+multi_apid(aind).sizes  ; AEE 7/25/03
      sizes= STRTRIM((STR_SEP(multi_apid(aind).sizes,','))(0),2)
      sizes= LONG(str_sep(sizes,' ')/8.0)
      sstr= 'PT_OS_SIZES ='
      FOR sz= 0, N_ELEMENTS(sizes)-1 DO sstr= sstr+' '+STRTRIM(sizes(sz),2)
      PRINTF, OUT, sstr

      ;PRINTF, OUT, 'PT_OS_PROC_TIMES = '+multi_apid(aind).proc_times
      ;PRINTF, OUT, 'PT_OS_PROC_TIMES = '+(STR_SEP(multi_apid(aind).proc_times,','))(0)
      ; Keep unique proc_times (for HI summed sequences that use 3 different ip tables):
      toks= STR_SEP(multi_apid(aind).proc_times,',')
      stoks= SHIFT(toks,1)
      dind= WHERE(toks NE stoks, dcnt)
      ptm= toks(0)
      FOR di= 1, dcnt-1 DO ptm= ptm+','+toks(dind(di))
      PRINTF, OUT, 'PT_OS_PROC_TIMES = '+ptm

      PRINTF, OUT, 'PT_FPS = '+STRTRIM(fps,2)   ; AEE - 1/14/04
      PRINTF, OUT, ';' & PRINTF, OUT, ';'

   ENDFOR ; AEE - Dec 05, 02
   ENDFOR		;** for every unique os_num

   CLOSE, OUT
   FREE_LUN, OUT
   WIDGET_CONTROL,mdiag,SET_VALUE='%%%GENERATE_IPT: (.../IO/IPT/'+sc+ipt_file_name+') Done.'
   PRINT,'%%%GENERATE_IPT: (../IO/IPT/'+sc+ipt_file_name+') Done.'

   os_arr= temp_os_arr ; AEE - 5/22/03 - restore os_arr to its original

END