Intermec 6100 Reference Guide

Page of 26
SECTION 3
Component Reference
DOS Signature Capture Utility Programmer’s Reference Guide    3-7
The output file contains binary data.  PL/N applications
should execute PUTCTL 1036 (PR_SETESC) and PUTCTL
776 (PR_TRANSPARENT) before printing the contents of
the output file, and execute PUTCTL 1037 (PR_NOESC)
and PUTCTL 777 (PR_FULL) afterward.
PL/N Programming Example
EXTERNALS
   NUMERIC FUNCTION INPUT
   NUMERIC FUNCTION PRINTCTL = PGAPR2P
   NUMERIC FUNCTION SPAWNDOS = IPFSDP6
   STRING  FUNCTION MID      = IPFMID6
CONSTANTS
   LINES_PER_PAGE = 54
LOCAL VARIABLES
   01 RESPONSE                BINARY BYTE
   FD SIGFD                   ;FD for signature print file
   01 SIGBUF                  PIC X(128)  ;Buffer for signature print file
   01 FRACTION                BINARY WORD ;Size of fractional record
   01 SIGLINES                BINARY WORD ;# of lines needed for signature
   01 SAVE_LAST               BINARY WORD ;Saved value of PRT.LAST
   
   01 RPT_COND                BINARY BYTE ;Result of PRINTCTL
   01 PRT_STATUS              BINARY WORD ;Parameter for PRINTCTL
. . .
; Execute the signature print utility.
SIGLINES = SPAWNDOS( ‘PSIGP0C.EXE’, ‘SIGNATUR.PCX SIGNATUR.PRN’ )
IF SIGLINES > 66 THEN
   ; An error occurred
   OUT (KBD) (KB_HOME)
   &  ‘SIGNATURE’, CRLF, 
   &  ‘PRINT ERROR!’, CRLF,
   &  ‘ERROR #’, SIGLINES, BEL, CRLF,
   &  ‘PRESS ENTER’
   RESPONSE = INPUT(S+F)
   RETURN
ENDIF
. . .
; Print the report.  Because PRINTCTL allows the report to be aborted,
; files must be opened and closed outside of the report procedure.
OPEN (SIGFD, SIGBUF) ME_NAME & ‘SIGNATUR.PRN’, ME_READ + ME_TRANSPARENT
. . .