P$GETFONT
The P$GETFONT library routine retrieves information on the current font.
Syntax 1
 CALL "P$GETFONT" USING logicalFont
Parameters
logicalFont
Group Item
Group item with the following structure:
 
01 LogicalFont.
   02  LF-Height          pic S9(5Binary(2).
   02  LF-Width           pic 9(5Binary(2).
   02  LF-Escapement      pic 9(5Binary(2).
   02  LF-Orientation     pic 9(5Binary(2).
   02  LF-WeightValue     pic 9(3Binary(2).
   02  LF-ItalicValue     pic x.
   02  LF-UnderlineValue  pic x.
   02  LF-StrikeoutValue  pic x.
   02  LF-CharSetValue    pic 9(3Binary(2).
   02  LF-OutPrecisValue  pic 9 Binary(2).
   02  LF-ClipPrecisValue pic 9(3Binary(2).
   02  LF-QualityValue    pic 9 Binary(2).
   02  LF-PitchValue      pic 9 Binary(2).
   02  LF-FamilyValue     pic 9 Binary(2).
   02  LF-FaceName        pic x(31).
 
Note - only these fields are supported:
- LF-Height [A]
- LF-Escapement
- LF-WeightValue
- LF-ItalicValue
- LF-UnderlineValue
- LF-StrikeoutValue
- LF-PitchValue
- LF-FaceName
[A] If the height value is greater than 0, the font mapper transforms this value into device units and matches it against the cell height of the available fonts. If the height value is 0, the font mapper uses a default height value when it searches for a match. If the height value is less than 0, the font mapper transforms this value into device units and matches its absolute value against the character height of the available fonts.
Syntax 2
 CALL "P$GETFONT" USING settingName1, settingValue1 
                       [settingName2, settingValue2] 
                       ... 
                       [settingNameN, settingValueN]
Parameters
settingName1
settingName2
...
settingNameN
PIC X(n)
Specifies the setting name.
Possible values are:
 
"Height" [A]
"Escapement"
"Weight"
"Italic"
"Underline"
"Strike Out"
"Pitch"
"Face Name"
settingValue1
settingValue2
...
settingValueN
PIC X(n) or PIC 9(n) depending on the value type
Receives the setting value.
[A] If the height value is greater than 0, the font mapper transforms this value into device units and matches it against the cell height of the available fonts. If the height value is 0, the font mapper uses a default height value when it searches for a match. If the height value is less than 0, the font mapper transforms this value into device units and matches its absolute value against the character height of the available fonts.