.PowerBASIC Command Syntax (PBWin10)

Category: .Reference Materials

Date: 02-16-2022

Return to Index


 
'This snippets contains a list of every PowerBASIC command,
'including the syntax as defined in the PowerBASIC Help file.
 
#Align boundary
#Bloat size_expression
#Compiler [PBCC | PBWIN] [version] [, [PBCC | PBWIN] [version]] [, ...]
#Compile {Exe | DLL} ["filename{.exe|.dll}"]
#Com DOC "This is specific information to be used in the Help String"
#Com HELP "MyProg.chm", &H1E00
#Com Name "LibName", 3.32
#Com GUID Guid$("{20000000-2000-2000-2000000000000002}")
#Com TLIB On|OFF
#Debug Code [On|+ | OFF|-]
#Debug Display [On|+ | OFF|-]
#Debug Error [On|+ | OFF|-]
#Debug Print string_expression
%Def({%numeric_equate | $string_equate})
#Dim {ALL | NONE}
#If [Not] {%equate | %Def({%numeric_equate | $string_equate}) |
expression}
  {statements}
[#ElseIf [Not] {%equate | %Def({%numeric_equate | $string_equate}) |
expression}
  {statements}]
[#Else
  {statements}]
#EndIf
#Include [ONCE] "filespec"
#Messages COMMAND
#Messages Notify
#Optimize [Size | SPEED]
#Option {VERSION3 | VERSION4 | VERSION5}
#Register {ALL | DEFAULT | NONE}
#Resource "filespec"
#Stack num_expr
#Tools [On|+ | OFF|-]
#Utility "any text for an external program"
y = ABS(numeric_expression)
Accel Attach hDlg, AccelTbl() TO hAccelHandle
a$ = Acode$(UnicodeStrExpression [,CodePage&])
AND q
y = Arrayattr(Arr(), AttrNum)
Array Assign Array() = param1 [,param2] [,�]
Array Delete Array([index]) [For Count] [, expression]
Array Insert Array([index]) [For Count] [, expression]
Numeric Array:  Array Scan Array([index]) [For Count], expression, TO lvar&
String arrays:  Array Scan Array ([index]) [For Count] [, FROM start TO End] [, Collate {UCASE | cstring}], expression, TO lvar&
Numeric Array:  Array Sort darray([index]) [For Count] [,TAGARRAY tarray()] [,{ASCEND | DESCEND}]
String Array:   Array Sort dArray([index]) [For Count] [,FROM start TO End] [,Collate {UCASE | cstring}] [,TAGARRAY tarray()] [,{ASCEND | DESCEND}]
Custom Sort Array:  Array Sort darray([index]) [For Count] [,TAGARRAY tarray()] ,CALL custfunc()
y = Asc(string_expression [, position&])
Asc(String, position&) = byte_expression
{! | Asm} opcode
y = Atn(numeric_expression)
Beep
result& = Bgr(red&, green&, blue&)
result& = Bgr(rgbexpr&)
s$ = Bin$(numeric_expression [, digits])
x& = Bitse(nexp, nexp, bitsize)
resultvar = Bits(datatype, expression)
bytevar  = BITS?(expression)
wordvar  = BITS??(expression)
dwordvar = BITS???(expression)
intvar   = BITS%(expression)
longvar  = BITS&(expression)
Bit Calc intvar, bitnumber, calcexprflag = Bit(intvar, bitnumber)
Bit {Set | Reset | TOGGLE} intvar, bitnumber
x$ = Build$(a$,b$,c$,d$...)
count& = CallSTKcount
sfname$ = CallSTK$(n)
CallSTK diskfilename$
Call Dword dwpointer [{BDECL | CDECL | SDECL} ()]
Call Dword dwpointer USING abc([arguments]) [TO result_var]
Call ProcName [([arguments])] [TO result_var]
Id& = Cbctl
CtlMsg& = Cbctlmsg
WindowHandle??? = Cbhndl
lParam& = Cblparam
wMsg& = Cbmsg
wParam& = Cbwparam
bytevar?          = CByt(numeric_expression)
currencyvar@      = CCur(numeric_expression)
currencyextvar@@  = CCux(numeric_expression)
doublevar#        = CDbl(numeric_expression)
doublewordvar???  = Cdwd(numeric_expression)
extendedvar##     = Cext(numeric_expression)
integervar%       = Cint(numeric_expression)
longintvar&       = Clng(numeric_expression)
quadintvar&&      = Cqud(numeric_expression)
singlevar!        = CSng(numeric_expression)
wordvar??         = CWrd(numeric_expression)
CtlID   = CB.Ctl
Ctlmsg  = CB.Ctlmsg
WinHndl = CB.Hndl
Value   = CB.lParam
Msg     = CB.Msg
Value   = CB.wParam
CodeMsg = CB.Nmcode
NmPtr   = CB.Nmhdr
NmStruc = CB.Nmhdr$
NmHndl  = CB.Nmhwnd
NmID    = CB.NmID
intvar = Ceil(numeric_expression)
ChDir path
ChDrive drive
y  = Choose(index&, choice1 [, choice2] ...)
y& = CHOOSE&(index&, choice1 [, choice2] ...)
y$ = CHOOSE$(index&, choice1 [, choice2] ...)
s$ = Chr$(expression [,expression] [,...])
s$ = Chr$(string_expression [,...])
s$ = Chr$(x& TO y& [,...])
Class Name  [$GUID]  [AS COM | AS EVENT]
  Instance ClassName AS String
  Class Method Code blocks...
    Interface Name $GUID  [AS EVENT]
    INHERIT IUNKNOWN
    Method AND Property Code blocks...
  End Interface
  EVENT SOURCE Interface-Name
End Class
Clipboard Get Bitmap  [TO] ClipVar [, ClipResult]
Clipboard Get OEMtext [TO] StrgVar [, ClipResult]
Clipboard Get Text    [TO] StrgVar [, ClipResult]
Clipboard Get Unicode [TO] StrgVar [, ClipResult]
Clipboard Reset [, ClipResult]
Clipboard Set Bitmap  ClipHndl [, ClipResult]
Clipboard Set OEMtext StrgExpr [, ClipResult]
Clipboard Set Text    StrgExpr [, ClipResult]
Clipboard Set Unicode StrgExpr [, ClipResult]
Close [[#] filenum& [, [#] filenum&] ...]
a$ = ClsID$(ProgramID$)
address32 = CodePTR({Label | functionname | subname})
ComboBox Add hDlg, id&, StrExpr
ComboBox Delete hDlg, id&, item&
ComboBox Find hDlg, id&, item&, StrExpr TO datav&
ComboBox Find Exact hDlg, id&, item&, StrExpr TO datav&
ComboBox Get Count hDlg, id& TO datav&
ComboBox Get SelCount hDlg, id& TO datav&
ComboBox Get Select hDlg, id& TO datav&
ComboBox Get State hDlg, id&, item& TO datav&
ComboBox Get Text hDlg, id& [,item&] TO txtv$
ComboBox Get User hDlg, id&, item& TO datav&
ComboBox Insert hDlg, id&, item&, StrExpr
ComboBox Reset hDlg, id&
ComboBox Select hDlg, id&, item&
ComboBox Set Text hDlg, id&, item&, StrExpr
ComboBox Set User hDlg, id&, item&, NumExpr
ComboBox UnSelect hDlg, id&
s$ = Command$
s$ = Command$(ArgNum)
Comm Close [#] hComm [, [#] hComm ...]
lResult& = Comm([#] hComm, Comfunc)
Comm Line [Input] [#] hComm, string_var
Comm Open "COMnAS [#] hComm
Comm Print [#] hComm, string_expression [;]
Comm Recv [#] hComm, count&, string_var
Comm Reset [#] hComm, FLOW
Comm Send [#] hComm, string_expression
Comm Set [#] hComm, Comfunc = value
Control Add classname$, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Button, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Check3State, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]Control Add Checkbox, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ComboBox, hDlg, id&, [items$()], x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Frame, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]]
Control Add Graphic, hDlg, id&, "", x&, y&, wide&, high&[, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Image, hDlg, id&, image$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ImageX, hDlg, id&, image$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ImgButton, hDlg, id&, image$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ImgButtonX, hDlg, id&, image$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Label, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Line, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ListBox, hDlg, id&, [items$()], x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ListView, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Option, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ProgressBar, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add ScrollBar, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add StatusBar, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Tab, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add TextBox, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add Toolbar, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Add TreeView, hDlg, id&, txt$, x, y, xx, yy [, [style&] [,[exstyle&]]] [[,] Call CallBack]
Control Disable hDlg, id&
Control Enable hDlg, id&
Control Get Check hDlg, id& TO lResult&
Control Get Client hDlg, id& TO wide&, high&
Control Get Loc hDlg, id& TO x&, y&
Control Get Size hDlg, id& TO wide&, high&
Control Get Text hDlg, id& TO txt$
Control Get User hDlg, id&, index& TO retvar&
Control Handle hDlg, id& TO hCtl&
Control Kill hDlg, id&
Control Post hDlg, id&, Msg&, wParam&, lParam&
Control Redraw hDlg, id&
Control Send hDlg, id&, Msg&, wParam&, lParam& [TO lResult&]
Control Set Check hDlg, id&, checkstate&
Control Set Client hDlg, id&, wide&, high&
Control Set Color hDlg, id&, foreclr&, backclr&
Control Set Focus hDlg, id&
Control Set Font hDlg, id&, fonthndl&
Control Set Image hDlg, id&, newimage$
Control Set ImageX hDlg, id&, newimage$
Control Set ImgButton hDlg, id&, newimage$
Control Set ImgButtonX hDlg, id&, newimage$
Control Set Loc hDlg, id&, x&, y&
Control Set Option hDlg, id&, minid&, maxid&
Control Set Size hDlg, id&, wide&, high&
Control Set Text hDlg, id&, txt$
Control Set User hDlg, id&, index&, usrval&
Control Show State hDlg, id&, showstate& [TO lResult&]
y = Cos(numeric_expression)
 
a$ = CSet$(string_expression, strlen& [USING ustring_expression])
Cset [ABS] result_var = string_expression [USING string_expression]
s$ = CurDir$[(drive$)]
bytevar?         = CVByt(stringexpr [, offset])
curvar@          = CVCur(stringexpr [, offset])
cuxvar@@         = CVCux(stringexpr [, offset])
doublevar#       = CVD  (stringexpr [, offset])
doublewordvar??? = CVDwd(stringexpr [, offset])
extendedvar##    = CVE  (stringexpr [, offset])
integervar%      = CVI  (stringexpr [, offset])
longintvar&      = CVL  (stringexpr [, offset])
quadintvar&&     = CVQ  (stringexpr [, offset])
singlevar!       = CVS  (stringexpr [, offset])
wordvar??        = CVWrd(stringexpr [, offset])
Count% = Datacount
Data ["]item["] [[, ["]item["]] ...]
Date$ = s$      ' sets system date according to s$
s$ = Date$      ' s$ now contains system date
Declare {Sub | FunctionProcName [BDECL | CDECL | SDECL] [LIB "LibName"] [ALIAS "AliasName"] [([arguments])] [AS Type]
Declare CallBack Function ProcName [[()] As Long]
Declare Thread Function ProcName (ByVal var AS (Long | Dword}) AS {Long | Dword}
Decr variable
DEFtype letter_range [, letter_range] [, ...]
Desktop Get Client TO ncWidth&, ncHeight&
Desktop Get Loc TO x&, y&
Desktop Get Size TO ncWidth&, ncHeight&
Dialog Disable hDlg
Dialog Doevents [sleep&] [TO count&]
Dialog Enable hDlg
Dialog End hDlg [, lResult&]
Dialog Font [DEFAULT] fontname$ [,points&, style&, charset&]
Dialog Get Client hDlg TO wide&, high&
Dialog Get Loc hDlg TO x&, y&
Dialog Get Size hDlg TO x&, y&
Dialog Get Text hDlg TO titletext$
Dialog Get User hDlg, index& TO retvar&
Dialog New [Pixels, | Units,] hParent, title$, [x&], [y&], xx&, yy& [,[style&] [, [exstyle&]]] [,] TO hDlg
Dialog Pixels hDlg, x&, y& TO Units xx&, yy&
Dialog Post hDlg, Msg&, wParam&, lParam&
Dialog Redraw hDlg
Dialog Send hDlg, msg&, wParam&, lParam& [TO lResult&]
Dialog Set Client hDlg, x&, y&
Dialog Set Color hDlg, foreclr&, backclr&
Dialog Set Icon hDlg, newicon$
Dialog Set Loc hDlg, x&, y&
Dialog Set Size hDlg, wide&, high&
Dialog Set Text hDlg, titletext$
Dialog Set User hDlg, index&, usrval&
Dialog Show Modal hDlg [[,] Call CallBack] [TO lResult&]
Dialog Show Modeless hDlg [[,] Call CallBack] [TO lResult&]
Dialog Show State hDlg, showstate& [TO lResult&]
Dialog Units hDlg, x&, y& TO Pixels xx&, yy&
Arrays:
Dim var[(subscripts)] [AS [Global | Instance | Local | Static | Threaded]Type] [PTR | POINTER] [AT address] [, ...]
Dim var[(subscripts)] ' var may include a type-specifier
Scalar variables:
Dim var AS [Global | Instance | Local | Static | ThreadedType [PTR|POINTER] [, ...]
Dim var  ' var must include a type-specifier
Dir$ Close
file$ = Dir$(mask$ [, [ONLY] attribute&, TO DirDataVar])
file$ = Dir$([Next] [TO DirDataVar])
bytes&& = DiskFree(drive$)
bytes&& = DiskSize(drive$)
Display Browse [hParent], [xpos], [ypos], title$, start$, flags TO folder$
Display Color [hParent], [xpos], [ypos], firstcolor, custcolors, flags TO
color&
Display Font [hParent], [xpos], [ypos], defname$, defpoints&, defstyle&,flags& TO fontname$, points&, style& [,color&, charset&]
Display OpenFile [hParent], [xpos], [ypos], title$, folder$, filter$, start$, defextn$, flags TO filevar$ [,countvar&]
Display SaveFile [hParent], [xpos], [ypos], title$, folder$, filter$, start$, defext$, flags TO filevar$ [,countvar&]
Do [{While | Until} expression]
  ...
  {statements}
  ...
  [Exit Loop]
  [Iterate Loop]
  ...
Loop {{While | Until} expression}
s$ = Environ$({parameter_string | n})
Environ envstring$
y = Eof([#] filenum&)
Eqv q
Erase Array[()]  [, Array[()]] ...
position$ = Erl$
nline = Erl
msg$ = Error$[(ErrNum)]
Error ErrNum
y = Err
Err = ErrNum
y = ErrClear
ErrClear
Dim oSource AS InterfaceName
Dim oEvent  AS EventInterface
Let oSource = NEWCOM CLSID $ClassId
Let oEvent  = Class "EventClass"
Events FROM oSource Call oEvent
...
Events End oEvent
EVENT SOURCE InterfaceName
f$ = Exe.Extn$
f$ = Exe.Full$
f$ = Exe.Name$
f$ = Exe.Namex$
f$ = Exe.Path$
Exit [For | Function | If | Do | Loop | Macro | Method | Property | Select | Sub | Try ]
Exit [, Exit] [, ...] [, Iterate]
y = Exp(n)
y = Exp2(n)
y = Exp10(n)
x$ = Extract$([start,] MainStr, [ANY] MatchStr)
Field # filenum, nSize AS fieldvar, [FROM] nStart TO nEnd AS fieldvar [,...]
Field DynamicStr, nSize AS fieldvar, [FROM] nStart TO nEnd AS fieldvar [,...]
Field Reset fieldvar [, ...]
Field String fieldvar [, ...]
lResult& = FileAttr([#] filenum&, fattr)
FileCopy sourcefile, destfile
a$ = FileName$(filenum&)
FileScan [#] fnum&, RECORDS TO y& [, Width TO x&]
y = Fix(numeric_expression)
Flush [[#] filenum& [, [#] filenum&] ...]
Font End fonthndl&
Font New fontname$ [,points!, style&, charset&, pitch&, escapement&] TO fhndl
x$ = Format$(num_expression [, [digits& | fmt$]])
For Counter = start TO stop [Step increment]
  .
  . {statements}
  .
Next [Counter]
h = Frac(float_expression)
x% = FreeFile
f$ = FuncName$
[CallBack | ThreadFunction FuncName [BDECL | CDECL | SDECL] [ALIAS "AliasName"] [([arguments])] [EXPORT | PRIVATE] [AS Type]
  [Dim | Local | Static variable list]
  {statements}
  [{FuncName | Function} = ReturnValue]
  {statements}
  [Exit Function]
  {statements}
End Function
x& = GetAttr(filespec$)
Random-Access files:
Get [#] filenum&, [Rec], [ABSVar
Get [#] filenum& [, Rec]
Binary files:
Get [#] filenum&, [RecPos], Var
Get [#] filenum&, [RecPos], Arr() [RECORDS rcds] [TO Count]
Get$ [#] filenum&, Count&, sVar$
GlobalMem Alloc  Count TO vHndl
GlobalMem Free   mHndl TO vHndl
GlobalMem Lock   mHndl TO vPtr
GlobalMem Size   mHndl TO vSize
GlobalMem UnLock mHndl TO vLocked
Global variable[()] [ AS Type] [, variable[()]] [, ...]
Global variable[()] [, variable[()]] [, ...] AS Type
GoSub {Label | linenumber}
GoSub Dword dwpointer
Graphic Arc (x1!, y1!) - (x2!, y2!), arcStart!, arcEnd! [, rgbColor&]
Graphic Attach hWin, Id [, Redraw]
Graphic Bitmap End
Graphic Bitmap Load BmpName$, nWidth&, nHeight& [,stretch&] TO hBmp???
Graphic Bitmap New nWidth&, nHeight& TO hBmp???
Graphic Box (x1!, y1!) - (x2!, y2!) [, [corner&] [, [rgbColor&] [,[fillcolor&] [, [fillstyle&]]]]]
Graphic Chr Size TO ncWidth!, ncHeight!
Graphic Clear [rgbColor& [, fillstyle&]]
Graphic Color foreground& [, background&]
Graphic Copy hbmpSource???, id& [, style&]
Graphic Copy hbmpSource???, id& TO (x!, y!) [, style&]
Graphic Copy hbmpSource???, id&, (x1!, y1!)-(x2!, y2!) TO (x!, y!) [,style%]
Graphic Detach
Graphic Ellipse (x1!, y1!) - (x2!, y2!) [, [rgbColor&] [,[fillcolor&] [, [fillstyle&]]]]
Graphic Font fontname$ [,points&, style&]
Graphic Get Bits TO bitvar$
Graphic Get Client TO ncWidth!, ncHeight!
Graphic Get DC TO hDC???
Graphic Get Lines TO linecount&
Graphic Get Loc TO x&, y&
Graphic Get Mix TO mixmode&
Graphic Get Pixel (x!, y!) TO rgbColor&
Graphic Get Pos TO x!, y!
Graphic Get PPI TO ncWidth&, ncHeight&
Graphic Get Scale TO x1!, y1!, x2!, y2!
Graphic ImageList (x!,y!), hLst, index&, overlay&, style&
Graphic Inkey$ TO string_variable
Graphic Input Flush
Graphic Input [prompt,] varlist
Graphic INSTAT TO numeric_variable
Graphic Line Input ["prompt"]  string_variable
Graphic Line [Step] [(x1!, y1!)] - [Step] (x2!, y2!)[, rgbColor&]
Graphic Paint [BORDER | Replace] [Step] (x!, y!) [, [rgbFill&] [,[rgbBorder&] [, [fillstyle&]]]]
Graphic Pie (x1!, y1!) - (x2!, y2!), arcStart!, arcEnd! [, [rgbColor&] [,[fillcolor&] [, [fillstyle&]]]]
Graphic Polygon points [,[rgbColor&] [, [fillcolor&] [,[fillstyle&] [,fillmode&]]]]
Graphic Polyline points [, rgbColor&]
Graphic Print expr [; expr] [;]
Graphic Redraw
Graphic Render BmpName$, (x1!, y1!)-(x2!, y2!)
Graphic Save BmpName$
Graphic Scale (x1!, y1!) - (x2!, y2!)
Graphic Scale Pixels
Graphic Set Bits bitexpr$
Graphic Set Focus
Graphic Set Font fonthndl&
Graphic Set Loc x&, y&
Graphic Set Mix mode&
Graphic Set Pixel [Step] (x!, y!) [, rgbColor&]
Graphic Set Pos [Step] (x!, y!)
Graphic Stretch hbmpSource???, id&, (x1!, y1!)-(x2!, y2!) TO (x3!,y3!)-(x4!,y4!) [, mix&, stretch&]
Graphic Style linestyle&
Graphic Text Size txt$ TO nWidth!, nHeight!
Graphic WaitKey$ [TO string_variable]
Graphic Width linewidth&
Graphic Window Click [hwin&] TO click&, x!, y!
Graphic Window End
Graphic Window caption$, x&, y&, nWidth&, nHeight& TO hWin???
id$ = GuidTxt$(guid16$)
id$ = Guid$[()]
id$ = Guid$(guidtext$)
s$ = Hex$(numeric_expression [, digits])
bResult?  = HiByt(sixteenbitvalue)
iResult% = HiInt(thirtytwobitvalue)
wResult?? = HiWrd(thirtytwobitvalue)
result = Hi(Type, value)
Host Addr [hostname$] TO ip&
Host Addr(index&) TO ip&
Host Name [ip&] TO hostname$
info& = IDispInfo.Code
info& = IDispInfo.CONTEXT
info$ = IDispInfo.DESC$
info$ = IDispInfo.HELP$
info$ = IDispInfo.SOURCE$
If integer_expression Then
  {statements}
[ElseIf integer_expression Then
  {statements}]
[Else
  {statements}]
End If
If integer_expression Then {Sub | Label | statements} [Else {Sub | Label | statements}]
var  = IIF(num_expression, truepart, falsepart)
var& = IIF&(num_expression, truepart&, falsepart&)
var$ = IIF$(num_expression, truepart$, falsepart$)
ImageList Add Bitmap hLst, hBmp [,hMsk] [TO data&]
ImageList Add Bitmap hLst, Bmp$ [,Msk$] [TO data&]
ImageList Add Icon hLst, hIcn [TO data&]
ImageList Add Icon hLst, Icn$ [TO data&]
ImageList Add Masked hLst, hBmp, rgb& [TO data&]
ImageList Add Masked hLst, Bmp$, rgb& [TO data&]
ImageList Get Count hLst TO data&
ImageList Kill hLst
ImageList New Bitmap|Icon width&, height&, depth&, initial& TO hLst
ImageList Set Overlay hLst, image&, overlay&
Imp q
Incr variable
sResult$ = InputBox$(prompt$ [[, title$], default$] [, xpos%, ypos%])
Input #filenum&, variable_list
Instance variable[()] [AS Type] [, variable[()]]
Instance variable[()] [, variable[()]] [, ...] AS Type
y& = Instr([n&,] MainString, [ANY] MatchString)
Interface IDBIND interfacename
  MEMBER {Call | Get | Set | Let} membername <dispid> ( [[OPTIONAL
      [IN | OUT | INOUT]] paramname <dispid> [AS Type] [,...]] )
      [AS {vartype | Interface}]
  [...]
End Interface
Interface interfacename [$GUID] [AS EVENT] [AS HIDDEN]
  [Method | PropertyName [(paramlist) [AS Type]
End Interface
y = Int(numeric_expression)
IsFalse expr
IsTrue expr
FileExists& = IsFile(FileName$)
IfaceValid = IsInterface(ObjectVar, InterfaceName)
ParamStatus = IsMissing(ParamVar)
oStatus = IsNothing(objectvar)
oStatus = IsObject(objectvar)
DialogExists&  = IsWin(hDlg&)
ControlExists& = IsWin(hParentDlg&, Ident&)
Iterate [Do | Loop | For]
A$ = Join$(Array(), {delim$ | BINARY})
Kill filespec
y& = LBound(Array [(dimension)])
y& = LBound(Array, dimension)
s$ = LCase$(string_expression [,ANSI | OEM])
s$ = Left$(string_expression, n&)
y& = Len(target)
[Let] variable  = expression
[Let] variable += expression
[Let] variable -= expression
[Let] variable *= expression
[Let] variable /= expression
[Let] variable \= expression
[Let] variable &= expression
[Let] variable AND= expression
[Let] variable Or= expression
[Let] variable Eqv= expression
[Let] variable Imp= expression
[Let] variable Mod= expression
[Let] variable XOR= expression
[Let] objvar = Object expression
[Let] typevar = typevar
[Letvariant = variant expression
Function { LibMain | DLLmain } ( _
  ByVal hInstance AS Dword, _
  ByVal lReason As Long, _
  ByVal lReserved As Long ) As Long
Line Input #filenum&, string_variable
Line Input #filenum&, Arr$() [RECORDS rcds] [TO Count]
ListBox Add hDlg, id&, StrExpr
ListBox Delete hDlg, id&, item&
ListBox Find hDlg, id&, item&, StrExpr TO datav&
ListBox Find Exact hDlg, id&, item&, StrExpr TO datav&
ListBox Get Count hDlg, id& TO datav&
ListBox Get SelCount hDlg, id& TO datav&
ListBox Get Select hDlg, id& [,item&] TO datav&
ListBox Get State hDlg, id&, item& TO datav&
ListBox Get Text hDlg, id& [,item&] TO txtv$
ListBox Get User hDlg, id&, item& TO datav&
ListBox Insert hDlg, id&, item&, StrExpr
ListBox Reset hDlg, id&
ListBox Select hDlg, id&, item&
ListBox Set Text hDlg, id&, item&, StrExpr
ListBox Set User hDlg, id&, item&, NumExpr
ListBox UnSelect hDlg, id& [,item&]
ListView Delete Column hDlg, id&, col&
ListView Delete Item hDlg, id&, row&
ListView Find hDlg, id&, row&, StrExpr TO datav&
ListView Find Exact hDlg, id&, row&, StrExpr TO datav&
ListView Fit Content hDlg, id&, col&
ListView Fit Header hDlg, id&, col&
ListView Get Column hDlg, id&, col& TO datav&
ListView Get Count hDlg, id& TO datav&
ListView Get Header hDlg, id&, col& TO txtv$
ListView Get Mode hDlg, id& TO datav&
ListView Get SelCount hDlg, id& TO datav&
ListView Get Select hDlg, id& [,row&] TO datav&
ListView Get State hDlg, id&, row&, col& TO datav&
ListView Get StyleXX hDlg, id& TO datav&
ListView Get Text hDlg, id&, row&, col& TO txtv$
ListView Get User hDlg, id&, row& TO datav&
ListView Insert Column hDlg, id&, col&, StrExpr, width&, format&
ListView Insert Item hDlg, id&, row&, image&, StrExpr
ListView Reset hDlg, id&
ListView Select hDlg, id&, row&, [col&]
ListView Set Column hDlg, id&, col&, NumExpr
ListView Set Header hDlg, id&, col&, StrExpr
ListView Set Image hDlg, id&, row&, NumExpr
ListView Set Image2 hDlg, id&, row&, NumExpr
ListView Set ImageList hDlg, id&, hLst, NumExpr
ListView Set Mode hDlg, id&, NumExpr
ListView Set Overlay hDlg, id&, row&, NumExpr
ListView Set StyleXX hDlg, id&, NumExpr
ListView Set Text hDlg, id&, row&, col&, StrExpr
ListView Set User hDlg, id&, row&, NumExpr
ListView Sort hDlg, id&, col& [,options...]
ListView UnSelect hDlg, id&, row&, [col&]
ListView Visible hDlg, id&, row&
bResult? = LoByt(sixteenbitvalue)
Local variable[()] [AS Type] [, variable[()]] [...]
Local variable[()] [, variable[()]] [, ...] AS Type
Lock [#] filenum& [, {record&& | start&& TO end&&}]
qResult&& = Loc([#] filenum&)
y&& = Lof([#] filenum&)
y = Log(numeric_expression)
y = Log2(numeric_expression)
y = Log10(numeric_expression)
iResult% = LoInt(thirtytwobitvalue)
wResult?? = LoWrd(thirtytwobitvalue)
result = Lo(Type, value)
LPrint Attach device$
LPrint Close
LPrint Flush
LPrint FormFeed
device$ = LPrint$
LPrint [expression] [SPC(n)] [Tab(n)] [,] [;]
a$ = LSET$(string_expression, strlen& [USING ustring_expression])
LSet [ABS] result_var = string_expression [USING ustring_expression]
x$ = LTrim$(MainString [, [ANY] MatchString])
Single Line Macro:
Macro macroname [(prm1, prm2, ...)] = replacementtext
Multi-Line Macro:
Macro macroname [(prm1, prm2, ...)]
  [MACROTEMP ident1 [, ident2, ...]]
  Dim ident1 AS Type [, ident2 AS Type, ...]]
  {replacementtext}
  [Exit Macro]
  {replacementtext}
End Macro
Macro Function:
Macro Function macroname [(prm1, prm2, ...)]
  [MACROTEMP ident1 [, ident2, ...]
  Dim ident1 AS Type [, ident2 AS Type, ...]]
  {replacementtext}
  [Exit Macro]
  {replacementtext}
End Macro = returnexpression
value??? = MakDwd(loword, hiword)
value&   = MAKLNG(loword, hiword)
value??? = MakPtr(loword, hiword)
value%  = MakInt(lobyte, hibyte)
value?? = MakWrd(lobyte, hibyte)
resultvar = Mak(datatype, loworderval, highorderval)
Mat a1() = CON           'Set all elements of a1() to one
Mat a1() = CON(expr)     'Set all elements of a1() to value of expr
Mat a1() = IDN           'Establish a1() as an identity matrix
Mat a1() = ZER           'Set all elements of a1() to zero
Mat a1() = a2() + a3()   'Addition
Mat a1() = a2()          'Assignment
Mat a1() = INV(a2())     'Inversion
Mat a1() = (expr) * a2() 'Scalar Multiplication
Mat a1() = a2() - a3()   'Subtraction
Mat a1() = a2() * a3()   'Multiplication
Mat a1() = TRN(a2())     'Transposition
y  = Max(arg [, arg] ...)
y& = MAX&(arg& [, arg&] ...)
y$ = MAX$(arg$ [, arg$] ...)
s$ = Mcase$(string_expression [,ANSI | OEM])
Menu Add Popup, hMenu, txt$, hPopup, state& [, AT [BYCMD] pos&]
Menu Add String, hMenu, txt$, id&, state& [, AT [BYCMD] pos&] [, Call
Menu Attach hMenu, hDlg
Menu Delete hMenu, [BYCMD] pos&
Menu Draw Bar hDlg
Menu Get State hMenu, [BYCMD] pos& TO state&
Menu Get Text hMenu, [BYCMD] pos& TO txt$
Menu New Bar TO hMenu
Menu New Popup TO hPopup
Menu Set State hMenu, [BYCMD] pos&, state&
Menu Set Text hMenu, [BYCMD] pos&, txt$
[Class|OVERRIDEMethod Name [<DispID>] [ALIAS "altname"] (var AS
Type...) [AS Type]
  statements...
  Method = expression
End Method
Me.Method1(param)
s$ = Mid$(string_expression, start& [, length&])
Mid$(string_var, start& [, length&]) = replacement
y  = Min(arg, arg [, arg] ...)
y& = MIN&(arg&, arg& [, arg&] ...)
y$ = MIN$(arg$, arg$ [, arg$] ...)
DataTypeString$ = MkByt$(byte_expr)
DataTypeString$ = MkCur$(currency_expr)
DataTypeString$ = MkCux$(extended_currency_expr)
DataTypeString$ = MkD$(double_precision_expr)
DataTypeString$ = MkDwd$(double_word_expr)
DataTypeString$ = Mke$(extended_precision_expr)
DataTypeString$ = Mki$(integer_expr)
DataTypeString$ = Mkl$(long_integer_expr)
DataTypeString$ = Mkq$(quad_integer_expr)
DataTypeString$ = Mks$(single_precision_expr)
DataTypeString$ = Mkwrd$(word_expr)
MkDir path$
Mod q
MousePTR Style [TO var&]
lResult& = MsgBox(txt$ [, [style&], title$])
MsgBox txt$ [, [style%], title$]
? txt$ [, [style%], title$]
MyBase.Method1(param)
Name filespec1$ AS filespec2$
Not p
sResult$ = Nul$(Count)
lResult& = ObjActive(ProgID$)
Object Get Interface.member[.member.] [([[paramname =] param1 [, ...]])] TO ResultVar
Object Let Interface.member[.member.] [([[paramname =] param1 [, ...]])] = ValueVar
Object Set Interface.member[.member.] [([[paramname =] param1 [, ...]])] = ValueVar
Object Call Interface.member[.member.] [([[paramname =] param1 [, ...]])] [TO ResultVar]
Object RaiseEvent [Interface.]member[([[paramname =] param1 [, ...]])]
ObjectPointer??? = ObjPTR(objectvar)
text$ = ObjResult$([nexp&])
lResult& = ObjResult
s$ = Oct$(numeric_expression [, digits])
On Error GoTo {Label | line_number}
On Error Resume Next
On Error GoTo 0
On n GoSub {Label | line_number} [, {Label | line_number}] ...
On n GoTo {Label | line_number} [, {Label | line_number}] ...
Open filespec [For Mode] [ACCESS access] [Lock LockAS [#] filenum& [Len = record_size] [BASE = base]
Open Handle filehandle [For Mode] [ACCESS access] [Lock LockAS [#] filenum& [Len = record_size] [BASE = base]
Option Explicit
Or q
x& = ParseCount(string_expr [, {[ANY] string_delimiter | BINARY}])
a$ = Parse$(string_expr [, {[ANY] string_delimiter | BINARY}], index&)
Parse main$, array$() [, {[ANY] delim$ | BINARY}]
fil$ = PathName$(director, filespec$)
fil$ = PathScan$(director, filespec$[, pathspec$])
#PBForms named_block_marker
Function PBLibMain [()] [As Long]
Function PBMain [()] [As Long]
numvar = Peek([datatype,] address???)
strvar = Peek$([ASCIIZ,] address???, count&)
Poke  [datatype,] address???, datavalue
Poke$ [ASCIIZ,] address???, string_expr
ncPrinters& = PrinterCount
device$ = Printer$([Name | PORT], printernum&)
Print # fNum&
Print # fNum&, [ExpList] [SPC(n)] [Tab(n)] [,] [;] [...]
Print # fNum&, array$()
PROCESS Get PRIORITY TO lResult&
PROCESS Set PRIORITY Priority&
Profile diskfilename$
a$ = ProgID$(ClassID$)
ProgressBar Get Pos hDlg, id& TO datav&
ProgressBar Get Range hDlg, id& TO LoDatav&, HiDatav&
ProgressBar Set Pos hDlg, id&, pos&
ProgressBar Set Range hDlg, id&, lolimit&, hilimit&
ProgressBar Set Step hDlg, id&, step&
ProgressBar Step hDlg, id& [,incr&]
[OVERRIDEProperty Get|Set Name [<DispID>] [ALIAS "altname"] (var AS Type...) [AS Type]
  statements...
  Property = expression
End Property
Random-Access AND Binary files:
Put [#] fNum&, [RecPos], [ABS] VarName
Put [#] fNum& [, RecPos]
Binary files:
Put [#] fNum&, [RecPos], Arr()
Put$ [#] filenum&, string_expression
RaiseEvent ObjVar.Method()
Randomize [number]
value$ = Read$(n%)
ReDim [PRESERVEArray[(subscripts)] [AS Type] [AT address] [, ...]
RegExpr mask$ IN main$ [AT start&] TO iPos& [, iLen&]
Register variable [AS Type] [, variable [AS Type]]
RegRepl mask$ IN main$ WITH repl$ [AT start&] TO iPos&, newmain$
a$ = Remain$([position&,] main$, [ANY] match$)
x$ = Remove$(MainString, [ANY] MatchString)
REM
' comment text
; comment in an Inline Assembler statement
s$ = Repeat$(count&, string_expr)
Replace [ANY] MatchString WITH NewString IN MainString
Reset variable [, ...]
Reset Array() [, ...]
Reset Array(index) [, ...]
Resume [Label | Next]
sResult$ = Retain$(main$, [ANY] match$)
Return
result& = Rgb(red&, green&, blue&)
result& = Rgb(bgrexpr&)
s$ = Right$(string_expression, n&)
RmDir path
y = Rnd
y = Rnd(a, b)
y = Rnd(numeric_expression)
Rotate {LEFT | RIGHT} ivar, Count
x = Round(numeric_expression, n)
a$ = RSet$(string_expression, strlen& [USING ustring_expression])
RSet [ABS] result_var = string_expression [USING ustring_expression]
x$ = RTrim$(MainString [, [ANY] MatchString])
ScrollBar Get PageSize hDlg, id& TO datav&
ScrollBar Get Pos hDlg, id& TO datav&
ScrollBar Get Range hDlg&, id& TO LoDatav&, HiDatav&
ScrollBar Get TrackPOS hDlg, id& TO datav&
ScrollBar Set PageSize hDlg, id&, page&
ScrollBar Set Pos hDlg, id&, pos&
ScrollBar Set Range hDlg, id&, lolimit&, hilimit&
position&& = Seek([#] filenum&)
Seek [#] filenum&, position&&
Select Case [AS] [Long | CONST | CONST$] expression
Case [IS] testlist
  {statements}
[Case [IS] testlist
  {statements}]
[Case Else
  {statements}]
End Select
SetAttr filespec$, attribute
Seteof [#] filenum&
y = Sgn(numeric_expression)
ProcessId??? = Shell([HANDLES,] CmdString [, WndStyle])
Shell [HANDLES,] CmdString [, WndStyle, Exit TO exitcode&]
Shift [SIGNED] {LEFT | RIGHT} ivar, countexpr
y = Sin(numeric_expression)
x& = SizeOf(target)
Sleep m&
s$ = Space$(numeric_expression)
y = Sqr(numeric_expression)
Static variable[()] [AS Type] [, variable[()]]
Static variable[()] [, variable[()]] [, ...] AS Type
StatusBar Set Parts hDlg, id&, x& [,x&...]
StatusBar Set Text hDlg, id&, item&, style&, text$
s$ = StrDelete$(string_expression, start&, count&)
s$ = String$(Count, {Code | string_expression})
s$ = StrInsert$(Main$, sNew$, position&)
xPtr = StrPTR(StringVar)
s$ = StrReverse$(Main$)
s$ = Str$(numeric_expression [, digits])
Sub ProcName [BDECL | CDECL | SDECL] [ALIAS "AliasName"] [([arguments])] [EXPORT | PRIVATE] [Static]
  [Local variable_list]
  [Static variable_list]
  {statements}
  [Exit Sub]
  {statements}
End Sub
Swap var1, var2
var  = Switch(expr1, val1 [[, expr2, val2], ...])
var& = SWITCH&(expr1, val1& [[, expr2, val2&], ...])
var$ = SWITCH$(expr1, val1$ [[, expr2, val2$], ...])
sResult$ = Tab$(strtotab$, tabstop&)
Tab Delete hDlg, id&, page&
Tab Get Count hDlg, id& TO datav&
Tab Get Dialog hDlg, id&, page& TO Hndlv&
Tab Get Select hDlg, id& TO datav&
Tab Insert Page hDlg, id&, page&, image&, text$ [Call CallBackTO Hndlv&
Tab Reset hDlg, id&
Tab Select hDlg, id&, page&
Tab Set ImageList hDlg, id&, hLst
x& = Tally(MainString, [ANY] MatchString)
y = Tan(numeric_expression)
Tcp Accept [#] fNum& AS newfNum&
Tcp Close [#] fNum&
Tcp Line [Input] [#] fNum&, Buffer$
Tcp Notify [#] fNum&, {Send | Recv | Accept | CONNECT | CloseTO hWnd& As a Client:
Tcp Open {PORT p& | srvc$} AT host$ AS [#] fNum& [TIMEOUT timeoutval&] As a server:
Tcp Open SERVER [Addr ip&] {PORT p& | srvc$} AS [#] fNum& [TIMEOUT timeoutval&]
Tcp Print [#] fNum&, string_expression[;]
Tcp Recv [#] fNum&, count&, Buffer$
Tcp Send [#] fNum&, string_expression lCount& = ThreadCount
Threaded variable[()] [AS Type] [, variable[()]]
Threaded variable[()] [, variable[()]] [, ...] AS Type
thrdID& = ThreadID
Thread Close hThread TO lResult&
Thread Create FuncName (param) [StackSize,] [SuspendTO hThread
Thread Get PRIORITY hThread TO lResult&
Thread Resume hThread TO lResult&
Thread Set PRIORITY hThread, Priority&
Thread Status hThread TO lResult&
Thread Suspend hThread TO lResult&
 
y = Timer
To read the time:
s$ = Time$
To Set the time:
Time$ = string_expression
Tix QuadVar
Tix End QuadVar
Toolbar Add Button hDlg, id&, image&, cmd&, style&, text$ [AT item&]
[Call CallBack]
Toolbar Add Separator hDlg, id&, size& [AT item&]
Toolbar Delete Button hDlg, id&, [BYCMD] item&
Toolbar Get State hDlg, id&, [BYCMD] item& TO datav&
Toolbar Get Count hDlg, id& TO datav&
Toolbar Set ImageList hDlg, id&, hLst, type&
Toolbar Set State hDlg, id&, [BYCMD] item&, state&
Trace New fname$
Trace On
Trace Print string_expr
Trace OFF
Trace Close
TreeView Delete hDlg, id&, hItem
TreeView Get Bold hDlg, id&, hItem TO datav&
TreeView Get Check hDlg, id&, hItem TO datav&
TreeView Get Child hDlg, id&, hItem TO datav&
TreeView Get Count hDlg, id& TO datav&
TreeView Get Expanded hDlg, id&, hItem TO datav&
TreeView Get Next hDlg, id&, hItem TO datav&
TreeView Get Parent hDlg, id&, hItem TO datav&
TreeView Get Previous hDlg, id&, hItem TO datav&
TreeView Get Root hDlg, id& TO datav&
TreeView Get Select hDlg, id& TO datav&
TreeView Get Text hDlg, id&, hItem TO txtv$
TreeView Get User hDlg, id&, hItem TO datav&
TreeView Insert Item hDlg, id&, hPrnt, hIAftr, image&, simage&, txt$ TO hItem
TreeView Reset hDlg, id&
TreeView Select hDlg, id&, hItem
TreeView Set Bold hDlg, id&, hItem, flag&
TreeView Set Check hDlg, id&, hItem, flag&
TreeView Set Expanded hDlg, id&, hItem, flag&
TreeView Set ImageList hDlg, id&, hLst
TreeView Set Text hDlg, id&, hItem, txt$
TreeView Set User hDlg, id&, hItem, NumExpr
TreeView UnSelect hDlg, id&
NewString$ = Trim$(OldString$ [, [ANY] CharsToTrim$])
Try
  {statements}
  [Exit Try]
  {statements}
CATCH
  {Error handling statements}
  [Exit Try]
  {Error handling statements}
[FINALLY
  {statements}
  [Exit Try]
  {statements}]
End Try
Type MyType [BYTE | WORD | Dword | QWORD] [FILL]
  [MemberName [(subscripts)] AS] TypeName
  [MemberName [(subscripts)] AS TypeName]
  [...]
End Type
Type Set mainvar = {typevar | stringexpr$} [USING ustring_expression]
y = UBound(Array [(dimension)])
y = UBound(Array, dimension)
s$ = UCase$(string_expression [,ANSI | OEM])
UCODEPAGE numexpr [TO prevpage&]
a$ = UCode$(AnsiStrExpression [,CodePage&])
UDP Close [#] fNum&
UDP Notify [#] fNum&, {Send | Recv | CloseTO hWnd& AS wMsg&
UDP Open [PORT p&] AS [#] fNum& [TIMEOUT timeoutval&]
UDP Recv [#] fNum&, FROM ip&, pNum&, Buffer$
UDP Send [#] fNum&, AT ip&, pNum&, string_expression
Union UnionName
   MemberName [(subscripts)] AS TypeName
  [MemberName [(subscripts)] AS TypeName]
  [...]
End Union
UnLock [#] filenum& [, {record&& | start&& TO end&&}]
sResult$ = Using$(fmtmask$, expr [, expr [, ...]])
y = Val(string_expression)
numericvar = VariantVT(vrntvar)
numericvar = Variant#(vrntvar)
stringvar = Variant$(vrntvar)
y = VarPTR(variable)
x = Verify([start&,] MainString, MatchString)
While integer_expression
  {statements}
  [Exit Loop]
  {statements}
Wend
Window Get Id hWin TO datav&
Window Get Parent hWin TO datav&
Function {WinMain | MAIN} ( _
    ByVal  hInstance   AS Dword, _
    ByVal  hPrevInst   AS Dword, _
    ByVal  lpszCmdLine As AsciiZ PTR, _
    ByVal  nCmdShow    As Long ) As Long
WRITE #filenum&
WRITE #filenum&, [expression [{;|,} expression] ...] [;|,]
XOR q
XPrint Arc (x1!, y1!) - (x2!, y2!), arcStart!, arcEnd! [, rgbColor&]
XPrint Attach {Choose | DEFAULT | PrinterName$} [,JobName$]
XPrint Box (x1!, y1!) - (x2!, y2!) [, [corner&] [, [rgbColor&] [,[fillcolor&] [, [fillstyle&]]]]]
XPrint Cancel
XPrint Chr Size TO ncWidth!, ncHeight!
XPrint Close
XPrint Color foreground& [, background&]
XPrint Copy hbmpSource???, id& [, style&]
XPrint Copy hbmpSource???, id& TO (x!, y!) [, style&]
XPrint Copy hbmpSource???, id&, (x1!, y1!)-(x2!, y2!) TO (x!, y!) [,style%]
XPrint Ellipse (x1!, y1!) - (x2!, y2!) [, [rgbColor&] [, [fillcolor&] [,[fillstyle&]]]]
XPrint Font fontname$ [,points&, style&]
XPrint FormFeed
device$ = XPrint$
XPrint Get Client TO ncWidth!, ncHeight!
XPrint Get Collate TO collatestatus&
XPrint Get ColorMode TO colormode&
XPrint Get Copies TO copycount&
XPrint Get DC TO hDC???
XPrint Get Duplex TO duplexstatus&
XPrint Get Lines TO linecount&
XPrint Get Margin TO nLeft!, nTop!, nRight!, nBottom!
XPrint Get Mix TO mode&
XPrint Get Orientation TO orent&
XPrint Get Papers TO papers$
XPrint Get Paper TO papertype&
XPrint Get Pixel (x!, y!) TO rgbColor&
XPrint Get Pos TO x!, y!
XPrint Get PPI TO x&, y&
XPrint Get Quality TO qual&
XPrint Get Scale TO x1!, y1!, x2!, y2!
XPrint Get Size TO nWidth!, nHeight!
XPrint Get Trays TO trays$
XPrint Get Tray TO papertray&
XPrint ImageList (x!,y!), hLst, index&, overlay&, style&
XPrint Line [Step] [(x1!, y1!)] - [Step] (x2!, y2!)[, rgbColor&]
XPrint Pie (x1!, y1!) - (x2!, y2!), arcStart!, arcEnd! [, [rgbColor&] [,[fillcolor&] [, [fillstyle&]]]]
XPrint Polygon points [, [rgbColor&] [, [fillcolor&] [, [fillstyle&] [,fillmode&]]]]
XPrint Polyline points [, rgbColor&]
XPrint Render BmpName$, (x1!, y1!)-(x2!, y2!)
XPrint Render BmpName$, (x1!, y1!)-(x2!, y2!)
XPrint Set Collate numrexp
XPrint Set ColorMode numrexp
XPrint Set Copies numrexp
XPrint Set Duplex numrexp
XPrint Set Font fonthndl&
XPrint Set Mix mode&
XPrint Set Orientation orent&
XPrint Set Paper papertype&
XPrint Set Pixel [Step] (x!, y!) [, rgbColor&]
XPrint Set Pos [Step] (x!, y!)
XPrint Set Quality qual&
XPrint Set Tray numrexp
XPrint [expression] [;]
XPrint Stretch Hndl, Id, (x1,y1)-(x2,y2) TO (x3,y3)-(x4,y4) [,Mix,Stretch]
XPrint Style linestyle&
XPrint Text Size txt$ TO nWidth!, nHeight!
XPrint Width ncPixels&
 
'gbs_00956
'Date: 03-10-2012


created by gbSnippets
http://www.garybeene.com/sw/gbsnippets.htm