|
How to wrap Sendmail/iX Stop! Go back and read the
Inside VESOFT column if you havent done so already.
This month Im collaborating with myself on the Inside VESOFT
column to bring you an extravaganza of technical geekiness. The
command file in that column will generate all the header information
for a report to go through the Sendmail program. The program in this
column will find the report, run it through a translation step into
HTML, and then send the results through the Sendmail program. We get to see a couple of things illustrated in our program code in Figure 1 below. The first is how to create a very specific LISTSPF command with its output redirected to a file which we then read back to find the target spool file. Consider the example code and the following statement: %COMIMAGE(BUILD
SPFFILE;REC=-80,1,F,ASCII;DISC=5000;TEMP#). What we have done is set
the spool priority of 5 as our candidate queue for Sendmail/iX. This
is arbitrary, but works for me. As part of this LISTSPF we will look
for any spool that is in a READY state, and was also created by this
job/session. This should pretty much narrow it down to whatever we
need. One of the features of this process is that you can have n
number of reports that are generated prior to running this program.
If you want different behavior then you will need to adjust the
process accordingly. Now there is one bit of
rather important code, which is the call to SPFCNV towards the end.
This particular sub-routine is proprietary to my company for some
products. Essentially what it does is convert carriage control
directives and escape sequences into HTML as best it can. This makes
the report even more readable, but you could control this by having
your reports output to disk instead, and not use carriage control or
escape sequences. You could just write it yourself, its not
that big a challenge. Remember that one of the challenges in e-mailing a report is that you want it to look the same on the screen as it does on paper. This means using fixed width fonts, which isnt all that straightforward to make a mail reader do, unless you use something like HTML where you can tell it the font characteristics. You will notice in the code where we send a !<PRE WIDTH=210!> to the file, this says that the HTML document is pre formatted with a width of 210, and to just leave it alone. You might also wonder about the ! next to the < and > symbols. This is to keep MPE from interpreting those symbols as I/O redirection, and to pass them on as is. The ! does not get put in the file. If you look at some of the CI variables that we are referencing, you will notice that they correspond to variables that were in our STREAMX command file in the Inside VEsoft column. All the rest of that stuff is boundaries and Sendmail controls and such. We do cleanup at the end to get rid of the spool files and disk files that we used as well. I hope youve enjoyed our foray into Internet e-mail this month. Dont forget that I would love to hear from you as well, so send in your ideas. Figure 1 $CONTROL USLINIT,BOUNDS IDENTIFICATION DIVISION. PROGRAM-ID. EMAILRPT. AUTHOR. Shawn M. Gordon. DATE-COMPILED. * ************************************************************ * This program does a redirection of a LISTSPF to a file * and then reads it back to find all the reports in this * process that will need to be formatted as HTML and sent * as email. * DEPENDENCIES * SU9004 for spool processing * EMAIL.CMD to generated email header file ************************************************************* * ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. HP-3000. OBJECT-COMPUTER. HP-3000. SPECIAL-NAMES. CONDITION-CODE IS CC. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT SPFFILE ASSIGN TO "SPFFILE". DATA DIVISION. FILE SECTION. FD SPFFILE RECORD CONTAINS 80 CHARACTERS. 01 SPFFILE-RECORD. 03 SR-SPOOLID PIC X(10). 03 PIC X. 03 SR-JOBNUM PIC X(08). 03 PIC X. 03 SR-FILEDES PIC X(08). 03 PIC XX. 03 SR-PRI PIC X(02). 03 PIC X. 03 SR-COPIES PIC X(06). 03 PIC X. 03 SR-LDEV PIC X(08). 03 PIC X. 03 SR-STATE PIC X(06). 03 PIC X. 03 SR-RSPFN PIC X(05). 03 SR-RECS REDEFINES SR-RSPFN. 05 SR-PAGES PIC X(05). 03 PIC X. 03 SR-OWNER PIC X(18). 03 SR-DT REDEFINES SR-OWNER. 05 SR-DATE PIC X(08). 05 PIC X. 05 SR-TIME PIC X(05). 05 PIC X(04). WORKING-STORAGE SECTION. 01 MPE-COMMAND PIC X(132) VALUE SPACES. 01 INPUT-FILE PIC X(30). 01 OUTPUT-FILE PIC X(30). 01 STATUS PIC S9(9) COMP. 01 COM-IMAGE. 03 COMMAND-IMAGE PIC X(255) VALUE SPACES. 03 PIC X VALUE %15. 01 COMMAND-ERROR PIC S9(4) BINARY VALUE 0. 01 ERR-PARM PIC S9(4) COMP VALUE 0. 01 MSG-LEVEL PIC S9(4) COMP VALUE 0. 01 VAR-NAME PIC X(40) VALUE SPACES. 01 VAR-INT PIC S9(9) COMP VALUE 0. 01 VAR-BOOL PIC S9(9) COMP VALUE 0. 01 VAR-STRING PIC X(255) VALUE SPACES. * 01 VAR-STATUS. 03 VS-1 PIC S9(4) COMP VALUE 0. 03 VS-2 PIC S9(4) COMP VALUE 0. PROCEDURE DIVISION. A0000-MACROS. * COMIMAGE takes one parameter to execute as MPE command * COMIMAGE2 will take 2 parameters to execute as MPE command $DEFINE %COMIMAGE= MOVE !1 TO COMMAND-IMAGE MOVE 2 TO MSG-LEVEL CALL INTRINSIC 'HPCICOMMAND' USING COM-IMAGE, COMMAND-ERROR, ERR-PARM, MSG-LEVEL# * $DEFINE %COMIMAGE2= INITIALIZE COMMAND-IMAGE STRING !1 DELIMITED BY SIZE !2 DELIMITED BY SIZE INTO COMMAND-IMAGE MOVE 2 TO MSG-LEVEL CALL INTRINSIC 'HPCICOMMAND' USING COM-IMAGE, COMMAND-ERROR, ERR-PARM, MSG-LEVEL# * USAGE - %GETVAR(MYVAR#). returns integer, boolean and strings * in their respective variables. $DEFINE %GETVAR= MOVE SPACES TO VAR-STRING MOVE ZEROES TO VAR-INT MOVE !1 TO VAR-NAME CALL INTRINSIC "HPCIGETVAR" USING VAR-NAME, VAR-STATUS, 1, VAR-INT, 2, VAR-STRING, 3, VAR-BOOL, 0# A1000-INIT. %GETVAR("send_mail"#). IF VAR-BOOL <> 1 STOP RUN. %GETVAR("RM"#). MOVE VAR-STRING TO OUTPUT-FILE. %COMIMAGE("BUILD SPFFILE;REC=-80,1,F,ASCII;DISC=5000;TEMP"#). %COMIMAGE("FILE SPFFILE=SPFFILE,OLDTEMP"#). STRING "LISTSPF O@;SELEQ=[(STATE='READY') AND (" "JOBNUM=#!HPJOBTYPE!HPJOBNUM) AND (PRI=5)]" ">*SPFFILE" DELIMITED BY SIZE INTO MPE-COMMAND. %COMIMAGE(MPE-COMMAND#). OPEN INPUT SPFFILE. A1000-EXIT. EXIT. A1100-READ. READ SPFFILE AT END GO TO C9000-EOJ. IF SR-SPOOLID(1:2) = "#O" PERFORM B1000-PROCESS-EMAIL THRU B1000-EXIT. GO TO A1100-READ. A1100-EXIT. EXIT. B1000-PROCESS-EMAIL. MOVE SPACES TO INPUT-FILE. STRING SR-SPOOLID(2:) DELIMITED BY SPACES ".OUT.HPSPOOL" DELIMITED BY SIZE INTO INPUT-FILE. MOVE SPACES TO MPE-COMMAND. STRING "SETVAR mail_file,'" DELIMITED BY SIZE SR-FILEDES DELIMITED BY SPACES ".HTML'" DELIMITED BY SIZE INTO MPE-COMMAND. * * ok, now we are going to write the MIME and HTML boundary stuff * for each report. %COMIMAGE(MPE-COMMAND#). %COMIMAGE("echo !mail_sep *mt"#). %COMIMAGE("echo x >>*mt"#). %COMIMAGE("echo !mail_sep >>*mt"#). %COMIMAGE2('echo Content-Type: text/plain;charset=us-ascii;'# ,' name="!mail_file" *mt'#). %COMIMAGE("echo Content-Transfer-Encoding: 8bit *mt"#). %COMIMAGE("echo *mt"#). %COMIMAGE("echo !>HTML!<!>PRE WIDTH=210!< *mt"#). %COMIMAGE("echo *mt"#). MOVE ZEROES TO STATUS. CALL "SPFCNV" USING INPUT-FILE, OUTPUT-FILE, STATUS. IF STATUS <> 0 DISPLAY 'Error in SPFCNV: ' STATUS DISPLAY 'Input file : ' INPUT-FILE DISPLAY 'Output file : ' OUTPUT-FILE. %COMIMAGE("echo !>/HTML!< *mt"#). %COMIMAGE("DELETESPOOLFILE "#, SR-SPOOLID#). B1000-EXIT. EXIT. C9000-EOJ. %COMIMAGE("echo !mail_sep-- *mt"#). %COMIMAGE("XEQ SENDMAIL.PUB.SENDMAIL'-t'>!RM"#). %COMIMAGE("PURGE !RM"#). CLOSE SPFFILE. STOP RUN. Shawn Gordon, whose S.M. Gordon & Associates firm supplies HP 3000 utilities, has worked with 3000s since 1983.
Copyright The 3000 NewsWire. All rights reserved. |