C+ C NAME: C smei_skyd C PURPOSE: C Creates skymaps from individual SMEI data frames C CATEGORY: C camera/for/sky C CALLING SEQUENCE: program smei_skyd C INPUTS: C Input is controlled by command line arguments (see PROCEDURE). C C file with pattern C default: $DAT/smei/testcase/DATA_SMEI/c2pat_2004_140.grd C use SMEIDB? to get pattern from SMEI data base C OPTIONAL INPUTS: C -source=directory where the SMEI frames are located C default: SMEIDB? (the SMEI data base) C -destination= C directory where the output files are written. C default: $TUB C -help print some instructions and exit. C C -firstorbit= default: 7223 C -lastorbit= default: 7224 C Orbits firstorbit through lastorbit are processed C -lowfraction= default: 0.0 C -highfraction= default: 1.0 C Only frames inside orbitfraction range C [lowfraction,highfraction] are used C (highfraction MUST be larger than lowfraction). C C -camera= camera to be processed C default: 2 C -mode= frame mode to be processed C default: 2 for cameras 1 and 2; 1 for camera 3 C -level= frame mode to be processed C default: 2 C -grd output .grd files in addition to Fits file. C -keepglare do not remove glare C -overwrite create a new skymap if the Fits file already exists C -checkversion create a new skymap if the Fits file already exists, C but only if it has a lower version number. C (if -overwrite is set then -checkversion is ignored) C -version C -dumpversion C -avoidmoon C -avoidmoon=tx1,tx2,ty1,ty2 C -avoidvenus=tx1,tx2,ty1,ty2 C -avoidsun=tx1,tx2,ty1,ty2 C OUTPUTS: C INCLUDE: include 'dirspec.h' include 'openfile.h' include 'filparts.h' include 'smei_frm_layout.h' include 'smei_frm_hdr.h' include 'smei_frm_hdrok.h' include 'smei_skyd_dim.h' C CALLS: C smei_orbit_time2, Say, cInt2Str, BadI4, BadR4, ArrR8Bad C Str2Str, Int2Str, Dbl2Str, iFilePath, bOpenFile, iFreeLun C smei_skyd_make, smei_skyd_fts, smei_cal_init C smei_frm_ok, ForeignArgSet, smei_frm_read, Time2Str C smei_frm_getlist, smei_orbit2, smei_foreign, iHideLogical C iOSDeleteFile, iSetFileSpec, iGetFileSpec, ArrI4Copy C smei_hdr_str, smei_skyd_init, smei_skyd_sky, cDbl2Str C EXAMPLE: C To run the testcase: C C smei_skyd $DAT/smei/testcase/DATA_SMEI C PROCEDURE: C > A call to smei_skyd has the structure: C C smei_skyd C -keyword1= -keyword2= .... C C > Large-scale flatfields are read from $SMEIDB/flatfield (one of C c1_clsff.fts.gz, c2_clsff.fts.gz or c3_clsff.fts.gz. C C Old HTM grid versus new equatorial/polar grid C --------------------------------------------- C C The linear dimension of pixels on the sky is ~0.05*2^mode (so 0.05, C 0.1 and 0.2 degrees for mode 0,1,2, respectively). Or in terms of area C on the sky 9*4^mode, or 9,36 and 144 arcmin^2 for mode 0,1,2. C C The HTM grid was used at level 11 for mode 1,2 and at level 12 for mode 0. C The area of nodes in the HTM grid is 3 to 7.3 arcmin^2 at level 11, and C 0.86 to 1.8 arcmin^2 at level 12. C C The final skymaps have a basic resolution of 0.1 degrees on the sky or C 36 arcmin^2 per skybin. This is level 1 in the new setup. Higher levels C are subdivisions of this grid, i.e. level n has bins with linear C dimension of 0.1/n degrees, or area 36/n^2 arcmin^2. So n=3 in the new C setup provides about the same resolution as HTM level 11, and level 5 C is about the same as HTM level 12. C MODIFICATION HISTORY: C NOV-2004, Paul Hick (UCSD/CASS) C MAY-2005, Paul Hick (UCSD/CASS) C Added processing of command line keywords nped_min and ndark_min C to override the default test for accepting frames (based on setting C of flag by href=smei_base=). C SEP-2005, Paul Hick (UCSD/CASS) C Camera 3 glare removal is now also done using the glare model C for the multiplier, instead of using a few constants. C NOV-2005, Paul Hick (UCSD/CASS), V2.0 C Modified to use different glare maps for cameras 2 and 3. C NOV-2005, Paul Hick (UCSD/CASS), V2.1 C Added another low resolution map to output file (fraction C of orbit in seconds since start of orbit). C The lowres maps for the 'glare angles' are now always calculated. C They used to be set zero if glare subtraction was suppressed. C All lowres maps for camera 2 are run through GridSphere2D to C fill holes near the equatorial poles. C DEC-2005, Paul Hick (UCSD/CASS), V2.11 C Changed format of several entries in Fits header C Modified to deal with presence of -overwrite on cmd line C DEC-2005, Paul Hick (UCSD/CASS), V2.12 C Added keyword MODE to Fits header C Added processing of keyword to force overwrite of C skymaps with a lower version number. C Added keyword IMG_TYPE to Fits header C JAN-2006, Paul Hick (UCSD/CASS), V3.00 C Introduced new definition of orbit start times based on C spacecraft ephemeris data (see smei_sgp4_orbits.pro). C JAN-2006, Paul Hick (UCSD/CASS), V3.01 C Added keyword nshutter_open_skip to enable skipping of C frames after the shutter opens (see smei_frm_ok). C JAN-2006, Paul Hick (UCSD/CASS), V4.0 C Fixed bug in smei_skyd_sky (the slope of the background C near stars was incorrect due to a wrong array index). C Reduced memory footprint by only processing HTM nodes C on the sky near the frame being processed. C FEB-2006, Paul Hick (UCSD/CASS), V5.0 C Removed JHU HTM grid. C JUN-2006, Paul Hick (UCSD/CASS), V5.1 C Added smei_skyd_size subroutine to control size of votes arrays. C Added direction cosine angle in long dimension to skymap file. C Note that this changes the layout of the Fits skymap file. C JUN-2006, Paul Hick (UCSD/CASS), V5.2 C Added hdrok array to store selection criteria for frames. C These are now added to the primary Fits header of the skymap. C JUL-2006, Paul Hick (UCSD/CASS) C Fixed error in some of the comments for the map description C keyword for the polar maps. C Added Fits keyword STIME and ETIME to extension containing the time C STIME in seconds since the first frame used (these were only specified C in the main header). STIME is the time origin for the array. C JUL-2006, Paul Hick (UCSD/CASS), V5.3 C Added check for bad quaternions in smei_frm_ok (this is used to skip past C B-dot episodes during S/C anomalies, for instance). C Filled the 'bad pixel' map in smei_skyd_combine (this has been empty C since version 4.0). C OCT-2006, John Clover, Paul Hick (UCSD/CASS), V6.0 C Fixed problem near seam of map where start and end of orbit meet. C The orientation of camera 2 at the start of the orbit C is now used to draw a reference great circle on the sky. Near this C boundary pixels are tested individually to decide whether they are C part of the current orbit and should be dropped in the skymap. C Introduced torigin to keep track of the time origin for the C lowres time map. This is added to the Fits header of the time C map as keyword TORIGIN (used to be STIME). C Times tfirstfrm and tlastfrm are assigned the time of the first C and last frame, respectively, for which at least one pixel was C dropped in the skymap. These are written into the main header C of the skymap as keywords STIME and ETIME. C Added extra extension to lowres maps containg nr of pixels C contributing to each lowres bin. C NOV-2006, Paul Hick (UCSD/CASS), V6.01 C Bugfix in smei_frm_ok (exclusion zones for Sun, Moon and Venus C were not processed) C MAR-2007, Paul Hick (UCSD/CASS) C Added check for "bad pixel" mask presence for camera 3. C The "closed shutter" calibration pattern for camera 3 is different C depending on whether a "bad pixel" mask is in effect. C APR-2007, Paul Hick (UCSD/CASS), V6.1 C Added keyword CLNEDGE, set to .FALSE.. Should be set .TRUE. C when straylight from sky just outside the fov is removed. C MAY-2007, Paul Hick (UCSD/CASS), V6.2 C Added GridSphere calls to smooth low resolution maps C where only a few CCD pixels (< 3) contribute to a skybin. C MAY-2007, Paul Hick (UCSD/CASS), V6.21 C Bug fix in smei_frm_read (was not picking up name of orbital C pattern). C MAY-2007, Paul Hick (UCSD/CASS), V6.22 C Bug fix in smei_skyd_size (abort was skipped when memory pool C for votes was full). C JUN-2007, Paul Hick (UCSD/CASS), V6.23 C Recompiled after bugfix in smei_frm_read. C JUL-2007, Paul Hick (UCSD/CASS), V6.24 C Renamed Fits key SMEI_HTM to SMEI_SKY (software version number) C Added cmd line argument -c3mask (used for camera 3 in mode 1 C only) to control selection of calibration pattern (without or C with "bad-pixel" mask taken into account. C DEC-2007, Paul Hick (UCSD/CASS) C For single orbit runs the exit code for a successful run is now C 1 [new skymap (over)written] or 3 [no new skymap written, either C because there are zero frames in the orbit, or because a C a skymap existed already and was not overwritten]. C For multiple orbits the exit code a successful run is always 1 C (this also was the case for single orbit runs). C DEC-2007, Paul Hick (UCSD/CASS), V7.01 C Replaced keywords CX*,CY*,D_* keywords by WCS keywords C CRPIX*, CDELT*. Added other WCS keywords to make the C headers WCS compliant: CRVAL*, CTYPE*, CUNIT*, RADESYS, C EQUINOX, MJD-OBS and (polar maps only) LONPOLE. C Added keyword BAD_DATA to headers for lowres maps. C Added keyword GAIN with camera gain based on time C set in MJD-OBS and TIME. C Changed keyword CREATED to DATE (consistent with IDL) C JAN-2008, Paul Hick (UCSD/CASS), V7.02 C Added keywords SMEI_CAL and SMEI_ORB with version numbers C APR-2008, Paul Hick (UCSD/CASS), V7.03 C Removed comma from comment string for Fits keyword MAP. C JUL-2008, Paul Hick (UCSD/CASS) C Decreased setting of iSilent passed to smei_frm_ok C SEP-2008, Paul Hick (UCSD/CASS), V7.04 C Added cmd line argument sdark. C OCT-2008, Paul Hick (UCSD/CASS), V7.05 C Modifications to handling of transitions of c3 C "bad-pixel" masks (in href=smei_frm_c3mask_active). C NOV-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu), V7.06 C Added default box for rejection of frames with Sun C too close to the optical axis (in smei_frm_ok). C- character cSay*9 /'smei_skyd'/ double precision version /7.06d0/ logical ForeignArgSet logical bOpenFile logical smei_frm_read logical smei_frm_read_set_sdark logical smei_frm_ok character cDbl2Str*14 character cInt2Str*14 integer Str2Str integer Dbl2Str integer Time2Str integer BadI4 integer smei_frm_getlist parameter (nVar=5) character cVar(nVar)*(FIL__LENGTH) /nVar*' '/ character cArg *(FIL__LENGTH) character cStr *(FIL__LENGTH*2) character cName *(FIL__LENGTH) integer TBeg (2) integer TEnd (2) integer TLowExt (2) integer THighExt(2) integer TLowLtd (2) integer THighLtd(2) ! Fraction of orbits where we expect ! to no longer have partial frames double precision hdr (SMEI__HDR_N) double precision hdrok(SMEI__HDROK_N) ! Orbital fractions: 0.15 starts 15% through orbit double precision forbit(2) ! Not used (passed to smei_foreign) ! forbit_ext includes fractions leading and trailing an orbit ! This defines an extended time range for selecting frames to process ! for a particular orbit. ! forbit_ltd omits fractions at leading and trailing end of an ! orbit. ! CCD frames earlier than forbit_ext[1] lie entirely ! outside the orbit (i.e. are part of the previous orbit) ! CCD frames between forbit_ext[1] and forbit_ltd[1] (near ! the start of an orbit) are checked pixel by pixel to decide ! whether the pixel lies inside or outside the orbit. Only pixels ! inside the orbit are added to the skymap ! CCD frames between forbit_ltd[1] and orbit_ltd[2] ! are added to the skymap as is (no checking of individual ! pixels is done. ! CCD frames between forbit_ltd[1] and forbt_extended[1] (near ! the end of an orbit) are checked pixel by pixel to decide ! whether the pixel lies inside or outside the orbit. Only pixels ! inside the orbit are added to the skymap ! CCD frames later than forbit_ext[2] lie entirely outside the ! orbit (i.e. are part of the next orbit) double precision forbit_ext(2) /-0.20d0,1.20d0/ double precision forbit_ltd(2) / 0.25d0,0.70d0/ double precision dorbit real frame(SMEI__FRM_NPIX) logical bOneSky logical bDig logical bGoAhead logical bOnTheFly logical bFirstFrm logical bNewSkymap iBad = BadI4() rBad = BadR4() ! Pick up command line arguments ! cVar(2) is name of pattern file, or blank string ! cVar(3) is source directory ! cVar(4) is destination directory ! cVar(5) is used later to store the name of the orbital pattern call smei_foreign(4,cVar(2),cVar(3),cVar(4),0,TBeg,TEnd,forbit,icam,mode,cArg) if (ForeignArgSet(cArg,'help')) then write (*,'(3X,A,T38,A)') cSay,' ', & ' ',' ', & ' '//cSwitch(:iSwitch)//'start_time=' ,SMEI__UT_FORMAT//', orbit nr', & ' '//cSwitch(:iSwitch)//'stop_time=' ,SMEI__UT_FORMAT//', orbit nr', & ' '//cSwitch(:iSwitch)//'camera=<1,2,3>' ,' ', & ' '//cSwitch(:iSwitch)//'mode=<0,1,2>' ,'default: 2 for cam 1,2; 1 for cam 3', & ' '//cSwitch(:iSwitch)//'source=' ,'default: SMEIDB?', & ' '//cSwitch(:iSwitch)//'digsource' ,'default: off (on for SMEIDB?)', & ' '//cSwitch(:iSwitch)//'destination=' ,'default: $TUB', & ' '//cSwitch(:iSwitch)//'level=' ,'default: 3 (mode 1/2) or 5 (mode 0)', & ' '//cSwitch(:iSwitch)//'onesky' ,'default: off', & ' '//cSwitch(:iSwitch)//'keepglare' ,'default: off', & ' '//cSwitch(:iSwitch)//'silent=<0,1,2,3>' ,'default: 0, less info for high value', & ' '//cSwitch(:iSwitch)//'nped_min=' ,'overrides default frame selection', & ' '//cSwitch(:iSwitch)//'ndark_min=' ,'overrides default frame selection', & ' '//cSwitch(:iSwitch)//'sdark=<3,10>' ,'use smoothed dark current', & ' '//cSwitch(:iSwitch)//'version' ,'print version number and exit', & ' '//cSwitch(:iSwitch)//'dumpversion' ,'print version number and exit', & ' '//cSwitch(:iSwitch)//'overwrite' ,'overwrite skymaps', & ' '//cSwitch(:iSwitch)//'checkversion' ,'overwrite skymaps with lower version number', & ' '//cSwitch(:iSwitch)//'nshutter_open_skip' ,'number of frames skipped after shutter opens', & ' '//cSwitch(:iSwitch)//'skip_onthefly' ,'do not use on-the-fly pattern for c3/m1', & ' '//cSwitch(:iSwitch)//'avoidsun=tx1,tx2,ty1,ty2' ,'omit frames where Sun is too bright', & ' '//cSwitch(:iSwitch)//'avoidmoon=tx1,tx2,ty1,ty2' ,'omit frames where Moon is too bright', & ' '//cSwitch(:iSwitch)//'avoidvenus=tx1,tx2,ty1,ty2' ,'omit frames where Venus is too bright', & ' '//cSwitch(:iSwitch)//'avoidmoon' ,'same as '//cSwitch(:iSwitch)//'avoidmoon=-42,42,-6.5,6.5', & ' '//cSwitch(:iSwitch)//'type=n' ,'0=mean, 1=median, default: 0', & ' '//cSwitch(:iSwitch)//'mean' ,'same as '//cSwitch(:iSwitch)//'type=0', & ' '//cSwitch(:iSwitch)//'median' ,'same as '//cSwitch(:iSwitch)//'type=1', & ' '//cSwitch(:iSwitch)//'keepglitches' ,'suppress glitch removal (CR,space debris)', & ' '//cSwitch(:iSwitch)//'c3mask=<0,1>' ,'cal pattern without/with "bad-pixel" mask', & ' '//cSwitch(:iSwitch)//'break=' ,'make skymaps after processing frames' call Say(cSay,'S','Stop','End syntax') end if if (ForeignArgSet(cArg,'dumpversion')) then ! Print version number write (*,'(F4.2)') version stop end if if (ForeignArgSet(cArg,'version')) ! Print version number & call Say(cSay,'S','Stop','Version '//cDbl2Str(version,2)// & 'Paul Hick (UCSD/CASS; pphick@ucsd.edu)') if (TBeg(1) .eq. iBad .or. TEnd(1) .eq. iBad) call Say(cSay,'E','times', & 'please, specify begin and end time#'// & 'type "'//cSay//' '//cSwitch(:iSwitch)//'help" for more info') if (icam .eq. iBad) call Say(cSay,'E','camera', & 'please, specify camera#'// & 'type "'//cSay//' '//cSwitch(:iSwitch)//'help" for more info') call ForeignI4Arg(cArg,'silent',0,iSilent) call ForeignI4Arg(cArg,'sdark',-1,idark ) call ForeignI4Arg(cArg,'break',-1,ibreak) bOneSky = ForeignArgSet(cArg,'onesky' ) bDig = ForeignArgSet(cArg,'digsource') bOnTheFly = icam .eq. 3 .and. mode .eq. 1 if (bOnTheFly) bOnTheFly = .not. ForeignArgSet(cArg,'skip_onthefly') if (bOneSky) then call smei_orbit2(TBeg,iorbit_first,dorbit) iorbit_first = nint(iorbit_first+dorbit) iorbit_last = iorbit_first i = 0 i = i+Time2Str(SMEI__UT_FORMAT,TBeg,cStr(i+1:)) i = i+Str2Str('-',cStr(i+1:)) i = i+Time2Str(SMEI__UT_FORMAT,TEnd,cStr(i+1:)) else call smei_orbit2(TBeg,iorbit_first,dorbit) iorbit_first = nint(iorbit_first+dorbit) call smei_orbit2(TEnd,iorbit_last ,dorbit) iorbit_last = nint(iorbit_last +dorbit) iorbit_last = max(iorbit_last-1,iorbit_first) i = 0 if (iorbit_last .eq. iorbit_first) then i = i+Str2Str('orbit' , cStr(i+1:))+1 i = i+Int2Str(iorbit_first, cStr(i+1:)) else i = i+Str2Str('orbits' , cStr(i+1:))+1 i = i+Int2Str(iorbit_first, cStr(i+1:))+1 i = i+Str2Str('-' , cStr(i+1:))+1 i = i+Int2Str(iorbit_last , cStr(i+1:)) end if end if i = i+Str2Str (', camera' , cStr(i+1:))+1 i = i+Int2Str (icam , cStr(i+1:)) i = i+Str2Str (', mode' , cStr(i+1:))+1 i = i+Int2Str (mode , cStr(i+1:)) i = i+Str2Str('#read from' , cStr(i+1:))+1 i = i+iHideLogical(cVar(3) , cStr(i+1:)) if (bDig) i = i+Str2Str(' (digging)', cStr(i+1:)) i = i+Str2Str('#write to' , cStr(i+1:))+2 i = i+iHideLogical(cVar(4) , cStr(i+1:)) if (cVar(2) .ne. ' ') then i = i+Str2Str('#pattern' , cStr(i+1:))+1 i = i+iHideLogical(cVar(2) , cStr(i+1:)) ! Pattern file end if if (icam .eq. 3 .and. mode .eq. 1 .and. .not. bOnTheFly) & i = i+Str2Str('#on-the-fly pattern not used', cStr(i+1:)) call Say(cSay,'I','do',cStr) if (.not. smei_frm_read_set_sdark(idark)) & call Say(cSay,'E','sdark','funny setting for sdark keyword') call smei_cal_init() if (bOneSky) then ! If bOneSky=.TRUE. then all pixels for all frames between ! TBeg and TEnd are dropped into the skymap call ArrI4Copy(2,TBeg,TLowExt ) call ArrI4Copy(2,TEnd,THighExt) call ArrR8Bad (2,forbit_ext) call ArrR8Bad (2,forbit_ltd) end if ! For bOneSky=.TRUE iorbit_first=iorbit_last do iorbit=iorbit_first,iorbit_last ! Loop over orbits bGoAhead = .TRUE. if (.not. bOneSky) then call smei_orbit_time2(iorbit,forbit_ext(1), TLowExt ) call smei_orbit_time2(iorbit,forbit_ext(2), THighExt) call smei_orbit_time2(iorbit,forbit_ltd(1), TLowLtd ) call smei_orbit_time2(iorbit,forbit_ltd(2), THighLtd) end if ! Get list of file names for current orbit (all frames between ! TLowExt and THighExt. ! The names are stored in file cStr (last argument) iframe = 0 nframe = smei_frm_getlist(TLowExt,THighExt,icam,mode,bDig,cVar(3),cStr) if (nframe .gt. 0) then ! Process all frames stored in file cStr. iRecl = 0 if (.not. bOpenFile(OPN__TEXT+OPN__REOPEN+OPN__NOMESSAGE,iU,cStr,iRecl)) then i = iOSDeleteFile(cStr) call Say(cSay,'E','#'//cStr,'error opening list with frame names') end if i = iScratchLun(iU) ! Mark cStr as scratch file read (iU,'(A)',iostat=i) cVar(1) ! Read file name of first frame do while (i .eq. 0 .and. bGoAhead) ! Process all frames in orbit if (smei_frm_read(OPN__REOPEN+OPN__NOMESSAGE,cVar(1),SMEI__FRM_NPIX,i,j,k,frame,hdr,headroom)) then i = iSetFileSpec(cVar(1)) i = iGetFileSpec(FIL__NAME,FIL__NAME,cName) if ( smei_frm_ok(cArg,cName,hdr,hdrok,iSilent-1) ) then ! Pick up name of calibration pattern, and (for cam 3, mode 1) the ! on-the-fly orbital (difference) pattern. call smei_hdr_str(SMEI__HDR_CAL_PATTERN,hdr,cVar(2)) if (bOnTheFly) call smei_hdr_str(SMEI__HDR_ORB_PATTERN,hdr,cVar(5)) ! Currently bGoAhead is only used when the first frame for an ! orbit is encountered to check whether the orbit needs to be ! processed or not. ! For the 2nd and later frames bGoAhead is always .TRUE. call smei_skyd_init(version,iorbit,TLowLtd,THighLtd,hdr,cVar,cArg,bGoAhead) ! Process all pixels in the FOV. Each pixel contributes a number ! of votes to the pool of active votes, and may add to the number ! of active nodes. if (bGoAhead) call smei_skyd_sky(hdr,iframe,frame) end if end if read (iU,'(A)',iostat=i) cVar(1) ! Read file name of next frame if (ibreak .ge. 0 .and. iframe .ge. ibreak) then i = 1 call Say(cSay,'I','breaking at',cInt2Str(iframe)) end if end do end if ! Orbit finished. iframe frames have been processed. ! If iframe not zero then process the orbit. bNewSkymap = .FALSE. if (.not. bGoAhead) then continue else if (iframe .eq. 0) then if (bOneSky) then i = 0 i = i+Time2Str(SMEI__UT_FORMAT,TLowExt,cStr(i+1:))+1 i = i+Str2Str ('-',cStr(i+1:))+1 i = i+Time2Str(SMEI__UT_FORMAT,THighExt,cStr(i+1:))+1 i = i+Str2Str ('has 0 frames',cStr(i+1:)) call Say(cSay,'I','period',cStr) else call Say(cSay,'I','orbit '//cInt2Str(iorbit),'has 0 frames') end if else if (bOneSky) then i = 0 i = i+Time2Str(SMEI__UT_FORMAT,TLowExt,cStr(i+1:)) i = i+Str2Str('-' , cStr(i+1:)) i = i+Time2Str(SMEI__UT_FORMAT,THighExt,cStr(i+1:))+1 i = i+Str2Str('has' , cStr(i+1:))+1 i = i+Int2Str(iframe , cStr(i+1:)) i = i+Str2Str('/' , cStr(i+1:)) i = i+Int2Str(nframe , cStr(i+1:))+1 i = i+Str2Str('frames', cStr(i+1:)) call Say(cSay,'I','period',cStr) else i = 0 i = i+Int2Str(iframe , cStr(i+1:)) i = i+Str2Str('/' , cStr(i+1:)) i = i+Int2Str(nframe , cStr(i+1:))+1 i = i+Str2Str('frames between fraction', cStr(i+1:))+1 i = i+Dbl2Str(forbit_ext(1), 3, cStr(i+1:))+1 i = i+Str2Str('and' , cStr(i+1:))+1 i = i+Dbl2Str(forbit_ext(2), 3, cStr(i+1:)) call Say(cSay,'I','orbit '//cInt2Str(iorbit),cStr) end if call smei_skyd_make() ! Make final maps call smei_skyd_fts(version,forbit_ext,forbit_ltd,hdrok,nframe,iframe,ibreak) ! Write fits file bNewSkymap = .TRUE. ! Indicates a skymap was (over)written end if iU = iFreeLun(-iU) end do ! Loop over all orbits if (iorbit_first .eq. iorbit_last) then ! Single orbit run ! The exit code for a single orbit tells the skyd daemon that ! a new skymap has been written. if (bNewSkymap) then ! Exit code = 1: new skymap written call Say(cSay,'S','Stop','All done (new skymap)') else ! Exit code = 3: no new skymap written call Say(cSay,'I','Stop','All done (no new skymap)') end if else ! Multiple orbits run call Say(cSay,'S','Stop','All done')! Exit code = 1 end if end