isCOBOL Evolve : Appendices : Library Routines : WIN$PRINTER : WINPRINT-SET-ATTRIBUTE
WINPRINT-SET-ATTRIBUTE
The WINPRINT-SET-ATTRIBUTE function sets attributes for the next PDF created by writing on a file assigned to "-P PDF" or by using the Save As function in the print preview dialog.
This function overrides the default settings set in the configuration (see Print Configuration).
Note: The attributes are set only for the first PDF print performed after the call to this op-code. If you need to set the attributes also for other PDF print jobs, then you need to call the op-code before each one of them.
Syntax:
 CALL "WIN$PRINTER" USING WINPRINT-SET-ATTRIBUTE 
                          attributeName 
                          attributeValue
                   GIVING returnCode
Parameters:
WINPRINT-SET-ATTRIBUTE
Constant
 
attributeName
PIC X(n)
Identifies the attribute to set. Valid values are listed below.
attributeValue
PIC X(n)
Value for the attribute
List of supported attributes:
Attribute
Description and possible values
AUTHOR
The author of the PDF document. It can be any text.
ENCRYPTION
Numeric bitwise value where each bit sets a specific feature.
 
You can rely on the following data-items, defined in isprint.def, to activate the desired feature:
77 pdfcrypt-type pic 9(9) value 0.
78 pdfcrypt-no value 0.
78 pdfcrypt-std-40 value 1.
78 pdfcrypt-std-128 value 2.
78 pdfcrypt-aes-128 value 3.
78 pdfcrypt-no-metadata value x#08.
78 pdfcrypt-embedded-files-only value x#10.
 
78 pdfcrypt-allow-printing value x#0100.
78 pdfcrypt-allow-modify-content value x#0200.
78 pdfcrypt-allow-copy value x#0400.
78 pdfcrypt-allow-modify-annotations value x#0800.
78 pdfcrypt-allow-fill-in value x#1000.
78 pdfcrypt-allow-screenreaders value x#2000.
78 pdfcrypt-allow-assembly value x#4000.
78 pdfcrypt-allow-degraded-printing value x#8000.
78 pdfcrypt-all-permissions value x#FF00.
 
If this value is set to 0 then no encryption takes place.
Permissions are applied only if combined with a valid encryption, otherwise all-permissions is assumed.
 
Usage example:
 
  add pdfcrypt-std-128
      pdfcrypt-allow-printing
      giving
      pdfcrypt-type
  call "win$printer" using winprint-set-attribute
       "ENCRYPTION" pdfcrypt-type
 
The resulting PDF will be printable, but it will not be possible to add annotations or copy the text to clipboard.
EXPIRES
The custom property "Expires". It can be any text.
FONT_FOLDER
The folders where the fonts used in the PDF document are installed. You can specify multiple folders separated by pipe, e.g. "C:\myCustomFonts|C:\WINDOWS\Fonts". The fonts loaded from these folders are not marked as "embedded".
 
The following rule applies to fonts loaded via W$CREATEFONT: if the font referenced in the print job is not installed in the system, only the specific TTF file loaded by the routine is included in the PDF. If the font is installed in the system, instead, then also alternative versions of the font may be included in the PDF in order to render bold and italic styles.
FONT_FOLDER_EMBED
The folders where the fonts used in the PDF document are installed. You can specify multiple folders separated by pipe, e.g. "C:\myCustomFonts|C:\WINDOWS\Fonts". The fonts loaded from these folders are marked as "embedded".
 
The following rule applies to fonts loaded via W$CREATEFONT: if the font referenced in the print job is not installed in the system, only the specific TTF file loaded by the routine is included in the PDF. If the font is installed in the system, instead, then also alternative versions of the font may be included in the PDF in order to render bold and italic styles.
JPEG
The compression applied to images in the PDF document. It can be "0" if you want to keep images unchanged (default) or it can range from "1" to "100" to indicate the image quality, where "1" is the lowest quality and "100" is the highest quality.
When this attribute is set, all images are internally translated to jpeg; this will remove transparency, if any.
KEYWORDS
The keywords of the PDF document. It can be any text.
OWNER_PASSWORD
The password of the owner of the document. If this value is not set, then a random password is created. It works only along with ENCRYPTION.
PDFA
Creates a PDF/A document following a specific standard. Possible values are "PDF/A-1A" and "PDF/A-1B", case insensitive.
This attribute must be set in conjunction with either FONT_FOLDER or FONT_FOLDER_EMBED as all the fonts must be available.
SUBJECT
The subject of the PDF document, it can be any text.
TITLE
The title of the PDF document, it can be any text.
USER_PASSWORD
The password of the user of the document. If this value is not set, then a default password is used as specified in the PDF specifics. It works only along with ENCRYPTION.
Note - if neither FONT_FOLDER nor FONT_FOLDER_EMBED are set, the PDF file will not use the fonts you specified through WINPRINT-SET-FONT.
Return Code:
returnCode can be any signed numeric data item and provides additional information:
1
Operation successful
WPRTERR-UNSUPPORTED
The WIN$PRINTER library routine is not supported.
WPRTERR-BAD-ARG
The WIN$PRINTER library routine has been called with bad parameters.