JGET-LAF-FONT
The JGET-LAF-FONT function returns the handle of a given font retrieved from the current LAF. The font handle must be destroyed by the program when it's done using the font.
This is the list of the known font entries that you can inquire:
Button.font
CheckBox.font
CheckBoxMenuItem.acceleratorFont
CheckBoxMenuItem.font
ColorChooser.font
ComboBox.font
EditorPane.font
FileChooser.listFont
FormattedTextField.font
InternalFrame.titleFont
Label.font
List.font
Menu.acceleratorFont
Menu.font
MenuBar.font
MenuItem.acceleratorFont
MenuItem.font
OptionPane.buttonFont
OptionPane.font
OptionPane.messageFont
Panel.font
PasswordField.font
PopupMenu.font
ProgressBar.font
RadioButton.font
RadioButtonMenuItem.acceleratorFont
RadioButtonMenuItem.font
ScrollPane.font
Slider.font
Spinner.font
TabbedPane.font
Table.font
TableHeader.font
TextArea.font
TextField.font
TextPane.font
TitledBorder.font
ToggleButton.font
ToolBar.font
ToolTip.font
Tree.font
Viewport.font
Syntax:
 CALL "J$GETFROMLAF" USING JGET-LAF-FONT 
                           lafEntry
                           WFONT-DATA
                    GIVING returnCode
Parameters:
JGET-LAF-FONT
Constant
 
lafEntry
PIC X(n) or string literal
Specifies the name of the font resource you want to inquire.
WFONT-DATA
Group Item
Structure that receives the characteristics of the font. This group item, defined in isfonts.def, has the following structure:
 
01  wfont-data.
    03 wfont-face-data.
       05 wfont-device                 handlevalue null.
          88 wfdevice-console          value null.
          88 wfdevice-printer          value 1.
       05 wfont-name                   pic x(33).
       05 wfont-char-set               pic x comp-x.
       05 wfont-size                   pic x comp-x.
       05 wfont-bold-state             pic x comp-x.
          88 wfont-bold                value 1false zero.
       05 wfont-italic-state           pic x comp-x.
          88 wfont-italic              value 1false zero.
       05 wfont-underline-state        pic x comp-x.
          88 wfont-underline           value 1false zero.
       05 wfont-strikeout-state        pic x comp-x.
          88 wfont-strikeout           value 1false zero.
       05 wfont-pitch-state            pic x comp-x.
          88 wfont-fixed-pitch         value 1false zero.
       05 wfont-family                 pic x comp-x.
    03 wfont-choose-data.
       05 wfont-choose-flags           pic x comp-x.
       05 wfont-choose-min-size        pic x comp-x.
       05 wfont-choose-max-size        pic x comp-x.
       05 wfont-choose-red             pic x comp-x.
       05 wfont-choose-green           pic x comp-x.
       05 wfont-choose-blue            pic x comp-x.
       05 wfont-choose-color-num       pic x comp-x.
    03 wfont-angle                     pic x(2comp-x.
    03 wfont-scale-x                   float value 0.
    03 wfont-scale-y                   float value 0.
 
Note - members not mentioned below are not used by this function.
 
wfont-device
Contains the device the function refers to. The value can be one of the condition names provided.
When wfdevice-console is set to true, the function will describe a font for the current screen configuration.
When wfdevice-printer is set to true, the function will describe a font for the current printer configuration.
 
wfont-name
Contains the name of the font.
 
wfont-size
Contains the size of the font.
 
 
Note - when the DPI is higher than 96, the returned font size might be too small, therefore it’s good practice to ignore this information and use a fixed font size (e.g. the same font size you’re using elsewhere in your programs).
 
wfont-bold-state
Contains the bold state of the font.
If the font is bold, wfont-bold is set to true.
 
wfont-italic-state
Contains the italic state of the font.
If the font is italic, wfont-italic is set to true.
 
wfont-underline-state
Contains the underline state of the font.
If the font is underlined, wfont-underline is set to true.
 
wfont-strikeout-state
Contains the strike-out state of the font.
If the font is stricken out, wfont-strikeout is set to true.
 
wfont-pitch-state
Contains the pitch state of the font.
If the font is a fixed-pitch font, wfont-fixed-pitch is set to true.
If the font is a variable-pitch font, wfont-fixed-pitch is set to false.
 
wfont-angle
Contains the angle at which the font will print. The value can range from the default of "0", which is the normal horizontal orientation, to "360", which is the same as "0". For example, to print at a 90-degree angle, set WFONT-ANGLE to "90". This feature works only when printing a font, not when displaying a font on screen.
 
wfont-scale-x
Contains the scale factor on the X coordinate. A value of 0 or 1 means that no scale is performed. This setting should be used only for print fonts (wfont-device = wfdevice-printer) that are not rotated (wfont-angle = 0), otherwise the effects are unpredictable.
 
wfont-scale-y
Contains the scale factor on the Y coordinate. A value of 0 or 1 means that no scale is performed. This setting should be used only for print fonts (wfont-device = wfdevice-printer) that are not rotated (wfont-angle = 0), otherwise the effects are unpredictable
Return code:
returnCode can be any signed numeric data item.
-1
Operation failed.
0
Operation successful.