HP 3000 Manuals

Index [ HP Pascal/iX Reference Manual ] MPE/iX 5.0 Documentation


HP Pascal/iX Reference Manual

Index

1
    16-bit characters, parsing   

A
    abs function   
    action, selecting an   
    actual parameters   
    addressing routines or data   
    addr predefined function   
    addtopointer predefined function   
    advancement of program flow   
    algorithm
       HP Pascal packing   
       Pascal/V packing   
    ALIAS compiler option   
    ALIGNMENT compiler option   
    allocation of storage   
    allocation procedures   
    AND operator   
    ANSI compiler option   
    ANSI/IEEE Extensions   
    appending
       files   
       strings   
    append procedure   
    arctan function   
    ARG_RELOCATION compiler option   
    arithmetic functions   
       abs   
       arctan   
       cos   
       exp   
       ln   
       sin   
       sqr   
       sqrt   
    arithmetic operators   
    array
       alignment requirements   
       constants   
       constructors   
       data type   
       designator   
       multi-dimensioned   
       printing information   
       selector   
    ASCII character code   
    ASCII character codes   
    assembler source file   
    assert function   
    ASSERT_HALT compiler option   
    assert procedure   
    assigning Boolean values   
    assignment compatibility   
    assignment statement   
    associate procedure   
    associating files   
    ASSUME compiler option   
       relationship of parameters, table   
    assumptions, testing   

B
    baddress function   
    base type   
    basic symbols   
    BEGIN..END statement   
    binary function   
    bit16 data type   
    bit32 data type   
    bit52 data type   
    bitsizeof predefined function   
    block   
    Boolean data types   
    Boolean expressions
       partial evaluation   
    Boolean operators   
    Boolean values
       assigning   
       false   
       true   
    building an intrinsic file   
    BUILDINT compiler option   
    buildpointer predefined function   
    byte address   
    bytes, moving   
    byte string comparison   

C
    call predefined procedure   
    CALL_PRIVILEGE compiler option   
    case constant   
    case selection   
    CASE statement   
    character codes, ASCII   
    character literals   
    char data type   
    char literal   
    CHECK_ACTUAL_PARM compiler option   
    CHECK_FORMAL_PARM compiler option   
    chr function   
    close procedure   
    closing files   
    cmpbytes function   
    code
       duplication   
       generation for routines   
       range checking   
    CODE compiler option   
    CODE_OFFSETS compiler option   
    coercion   
       noncompatible type   
       ordinal and pointer data types   
       ordinal type   
       other type   
       pointer type   
       reference type   
       representation type   
       storage type   
       structural type   
       value type   
    column width setting   
    comments, definition   
    comparing byte strings   
    compatibility
       assignment   
       Pascal on the Series 300 machines   
       string assignment   
       types   
    compiler directives   
    compiler limits   
    compiler option
       OPTIMIZE 'BASIC_BLOCKS_FENCE <num>'   
       OPTIMIZE 'BASIC_BLOCKS <num>'   
    compiler options   
       ALIAS   
       ALIGNMENT   
       ANSI   
       ARG_RELOCATION   
       ASSERT_HALT   
       ASSUME   
       BUILDINT   
       CALL_PRIVILEGE   
       CHECK_ACTUAL_PARM   
       CHECK_FORMAL_PARM   
       CODE   
       CODE_OFFSETS   
       CONVERT_MPE_NAMES   
       COPYRIGHT   
       COPYRIGHT_DATE   
       description   
       different on HP-UX and MPE/iX   
       ELSE   
       ENDIF   
       EXEC_PRIVILEGE   
       EXTERNAL   
       EXTNADDR   
       FONT   
       GLOBAL   
       GPROF   
       HEAP_COMPACT   
       HEAP_DISPOSE   
       HP3000_16   
       HP3000_32   
       HP_DESTINATION 'ARCHITECTURE'   
       HP_DESTINATION 'SCHEDULER'   
       HP Pascal   
       HP Standard   
       HP-UX   
       IF   
       INCLUDE   
       INCLUDE_SEARCH   
       INLINE   
       INTR_NAME   
       KEEPASMB   
       LINES   
       LIST   
       LIST_CODE   
       LISTINTR   
       list of   
       LITERAL_ALIAS   
       LOCALITY   
       locations, table of   
       LONG_CALLS   
       MAPINFO   
       MLIBRARY   
       MPE/iX   
       NLS_SOURCE   
       NOTES   
       OPTIMIZE   
       OS   
       OVFLCHECK   
       PAGE   
       PAGEWIDTH   
       PARTIAL_EVAL   
       POP   
       PUSH   
       RANGE   
       restoring option settings   
       RLFILE   
       RLINIT   
       S300_EXTNAMES   
       saving option settings   
       scopes, table of   
       SEARCH   
       SET   
       SHLIB_CODE   
       SHLIB_VERSION   
       SKIP_TEXT   
       SPLINTR   
       standard   
       STANDARD_LEVEL   
       STATEMENT_NUMBER   
       STRINGTEMPLIMIT   
       SUBPROGRAM   
       SYMDEBUG   
       SYSINTR   
       SYSPROG   
       system-dependent   
       system-independent   
       system programming   
       TABLES   
       TITLE   
       TYPE_COERCION   
       UPPERCASE   
       VERSION   
       VOLATILE   
       WARN   
       WIDTH   
       XREF   
    compiling
       conditionally   
       in ANSI standard Pascal   
       selected routines   
       syntax which does not conform to ANSI/ISO standards   
    compound statements   
    concatenation operator   
    conformance
       conformant array parameter   
       test   
    constant definition   
    constant expressions   
    constructing pointer values   
    constructor   
       record   
       restricted set   
       set   
       string   
    control characters   
    conversion
       implicit data   
       implicit data, table of   
    conversion functions
       numeric   
    converting file names   
    CONVERT_MPE_NAMES compiler option   
    copying characters in strings   
    COPYRIGHT compiler option   
    COPYRIGHT_DATE compiler option   
    cos function   
    cross referencing   
    crunched data types   
    CRUNCHED reserved word   

D
    data conversion   
    data pointer   
    data references   
    data structure
       integrity checking   
    data transfer   
    data types
       allocation and alignment of   
       bit16   
       bit32   
       bit52   
       Boolean   
       char   
       chart of   
       crunched   
       definition   
       enumerated   
       FUNCTION   
       integer   
       longint   
       longreal   
       mixing   
       pointer   
       pointers, short and long   
       PROCEDURE   
       real   
       set   
       shortint   
       simple   
       string   
       structured   
       subrange   
       system programming extensions   
    date, specifying in the copyright   
    deallocation of storage   
    deallocation procedures   
    debuggers   
    declaration part   
    declarations   
       array   
       constant definition   
       export   
       import   
       label   
       system programming extensions   
       variable   
    DEFAULT_PARMS routine options   
    defaults
       field widths, table of   
       parameters   
    definitions
       type   
    deleting characters from a string   
    directives   
       EXTERNAL   
       FORWARD   
    disassociate procedure   
    dispose procedure   
    disposing of storage   
    DIV operator   
    documenting a program   
    duplicating code   
    dynamic variable   

E
    elements of Pascal   
    ELSE compiler option   
    empty statement   
    empty string literal   
    ENDIF compiler option   
    enumerated data type   
    eof function   
    eoln function   
    error handling functions
       escapecode   
    error handling routines   
       escape   
    error messages   
    errors
       recovery   
       reflected in listing   
       trapping run-time   
       undetected   
    escapecode predefined function   
    escape predefined routine   
    EXEC_PRIVILEGE compiler option   
    exp function   
    export declaration   
    export declaration modules   
    EXPORT reserved word   
    expressions
       constant   
       definition   
       syntax   
       system programming extensions   
    extensible parameters   
    EXTENSIBLE routine options   
    extensions
       default reference parameter accessibility   
       parameter accessibility   
       system programming   
    EXTERNAL compiler option   
    EXTERNAL directive   
    EXTNADDR compiler option   

F
    false, Boolean value   
    fast_fill predefined procedure   
    fcall predefined procedure   
    field identifier   
    field list   
       fixed part   
       variant part   
    field widths, table of defaults   
    file buffer selector   
    file designator   
    file functions, table of   
    file procedures, table of   
    files
       appending   
       assembler source   
       associating files   
       closing   
       converting file names   
       definition   
       disassociate   
       eof   
       input/output (I/O)   
       intrinsic   
       intrinsic, building   
       intrinsic specification   
       listing   
       logical   
       opening   
       overprinting   
       packed   
       physical   
       resetting   
       rewriting   
       RL file initialization   
       sequential   
       text   
       textfiles   
       writing   
    final value   
    fixed part   
    FONT compiler option   
    font specification   
    FOR..DO statement   
    formal parameter   
    formal parameter congruency   
    formal parameter list   
    formal parameters   
       ANYVAR   
       READONLY   
    formats
       comparison between SPLINTER (SPL) and SYSINTR (HP Pascal)   
       SPLINTR (SPL)   
       SYSINTR(HP Pascal)   
    formatting of output   
    FORWARD directive   
    functional parameters   
    functions
       abs   
       arctan   
       arithmetic   
       baddress   
       binary   
       calls   
       chr   
       cmpbytes   
       conformance   
       cos   
       declaration   
       directives   
       eof   
       eoln   
       exp   
       FORWARD directive   
       function calls   
       function result   
       heading   
       hex   
       input/output (I/O)   
       lastpos   
       linepos   
       list of predefined   
       ln   
       maxpos   
       numeric conversion   
       octal   
       odd   
       ord   
       position   
       pred   
       recursion   
       return   
       round   
       scanuntil   
       scanwhile   
       sin   
       sqr   
       sqrt   
       str   
       string   
       strlen   
       strltrim   
       strmax   
       strpos   
       strrpt   
       strrtrim   
       succ   
       system programming extensions   
       transfer   
       trunc   
       waddress   

G
    generating code for routines   
    get procedure   
    GLOBAL compiler option   
    global variables   
    GOTO
       non-local   
    GOTO statement   
    GPROF compiler option   
    gprof utility   

H
    halting a program   
    halt procedure   
    haveextension predefined Boolean function   
    haveoptvarparm predefined Boolean function   
    heading of a program   
    heap   
    HEAP_COMPACT compiler option   
    HEAP_DISPOSE compiler option   
    hex function   
    hidden parameters   
    HP3000_16 compiler option   
    HP3000_32 compiler option   
    HP_DESTINATION 'ARCHITECTURE' compiler option   
    HP_DESTINATION 'SCHEDULER compiler option   
    HPFPconvert intrinsic   
    HP Pascal compiler options   
    HP Pascal Operators   
    HP Pascal packing algorithm   
    HP Standard compiler options   
    HP Symbolic Debugger   
    HP TOOLSET debugger   
    HP-UX
       available language features   
    HP-UX compiler options   

I
    identifier map   
    identifiers   
       definition   
       global   
       local   
       predefined, table of   
       scope of   
    IF compiler option   
    IF..THEN..ELSE statement   
    IF..THEN statement   
    implicit data conversion   
    import declaration modules   
    INCLUDE compiler option   
    INCLUDE_SEARCH compiler option   
    include-search patch, definition   
    including text in the source code   
    indirect recursion   
    initializing an RL file   
    initial value   
    INLINE compiler option   
    INLINE routine option   
    IN operator   
    input
       standard procedures and functions   
       textfiles   
    input (I/O)
       append   
       associate   
       close   
       disassociate   
       eof   
       eoln   
       formatting to textfiles   
       get   
       lastpos   
       linepos   
       maxpos   
       open   
       overprinting   
       page   
       position   
       prompt   
       put   
       read   
       readdir   
       readln   
       reset   
       rewrite   
       seek   
       standard procedures and functions   
       write   
       writedir   
       writeln   
    input textfiles   
    inserting characters into strings   
    integer
       sub-integer   
       super-integer   
    integer constant expressions   
    integer data type   
    integer literals   
    integral-types   
    intrinsic files
       building   
       listing the contents of   
       specification   
    intrinsics
       HPFPconvert   
    INTR_NAME compiler option   
    invariant conditions, specifying   
    ISO Pascal Extensions   

K
    KEEPASMB compiler option   

L
    label declaration   
    language elements   
       system programming extension   
    lastpos function   
    libraries
       shared   
    library, accessing   
    library modules   
    linepos   
    linepos function   
    LINES compiler option   
    lines, specifying number per page   
    LIST_CODE compiler option   
    LIST compiler option   
    listing
       contents of an intrinsic file   
       mneumonic   
    listing file   
    LISTINTR compiler option   
    LITERAL_ALIAS compiler option   
    literals
       char   
       character   
       empty string   
       integer   
       longreal   
       numeric   
       real   
       signed integer   
       string   
       unsigned integer   
    ln function   
    LOCALITY compiler option   
    locality names   
    local variables   
    logical files   
    LONG_CALLS compiler option   
    longint data type   
    longreal data type   
    longreal literals   
    longreal numbers   
    lowercase letter differentiation   

M
    MAPINFO compiler option   
    marking the allocation state   
    mark procedure   
    maxint   
       definition   
    maxpos function   
    migration routines   
    minint   
       definition   
    mixing data types   
    MLIBRARY compiler option   
    mneumonic listing, creation of   
    modification of variables   
    MOD operator   
    module
       definition   
    module definition   
       file specification   
    module definitions
       searching for   
    modules   
       export declaration   
       import declaration   
       library   
       separately compiled   
       variables   
    movebyteswhile procedure   
    move_fast predefined procedure   
    move_L_to_R predefined procedure   
    move procedures
       fast_fill   
       move_fast   
       moving left to right   
       moving right to left   
    move routines
       moving left to right   
    move_R_to_L predefined procedure   
    moving bytes   
    MPE
       available language features   
    MPE/iX
       available language features   
    MPE/iX compiler options   
    MPE V migration routines
       baddress   
       cmpbytes   
       movebyteswhile   
       scanuntil   
       scanwhile   
       waddress   
    multi-dimensioned arrays   
    multiple variants   

N
    names
       accessing a library or system routine   
       defining multiple internal names   
       locality specification   
       specifying an external name for a function   
       specifying an external name for a procedure   
       specifying an external name for a variable   
       upshifting   
    nesting blocks   
    new procedure   
    NIL   
    NLS_SOURCE compiler option   
    noncompatible type coercion   
    notes
       printing   
    NOTES compiler option   
    NOT operator   
    numeric conversion functions   
       binary   
       hex   
       octal   
    numeric literals   

O
    +Obbnum compiler option   
    object code
       generation   
       suppression   
    octal function   
    odd function   
    offset, definition   
    opening files   
    open procedure   
    operands   
       implicit conversion of   
       table of   
    operating systems
       HP-UX, available language features   
       MPE, available language features   
       MPE/iX, available language features   
       specification   
    operators   
       AND   
       arithmetic   
       Boolean   
       concatenation   
       DIV   
       dividend or divisor (DIV)   
       IN   
       MOD   
       modulus (MOD)   
       NOT   
       OR   
       pointer relational   
       precedence   
       relational   
       SET   
       set relational   
       simple relational   
       string relational   
       table of   
    optimization level specification   
    OPTIMIZE 'BASIC_BLOCKS_FENCE num' compiler option   
    OPTIMIZE 'BASIC_BLOCKS num' compiler option   
    OPTIMIZE compiler option   
    optimizer assumptions, specifying   
    options
       compiler   
       routine   
    ord function   
    ordinal data type coercion   
    ordinal data types   
       bit16   
       bit32   
       bit52   
       Boolean   
       char   
       enumerated   
       integer   
       subrange   
    ordinal functions   
       chr   
       ord   
       pred   
       succ   
    ordinal type coercion   
    ordinal type identifier   
    OR operator   
    OS compiler option   
    output
       formatting to textfiles   
       standard procedures and functions   
       textfiles   
    output (I/O)
       append   
       associate   
       close   
       disassociate   
       eof   
       eoln   
       formatting to textfiles   
       get   
       lastpos   
       linepos   
       maxpos   
       open   
       overprinting   
       page   
       position   
       prompt   
       put   
       read   
       readdir   
       readln   
       reset   
       rewrite   
       seek   
       standard procedures and functions   
       write   
       writedir   
       writeln   
    output textfiles   
    overflow checking   
    overprint   
    overprinting files   
    overprint procedure   
    overriding the UPPERCASE compiler option   
    OVFLCHECK compiler option   

P
    PAC array definition   
    PACK ARRAY definition   
    packed array   
    packed data types   
    packed files   
    PACKED reserved word   
    pack procedure   
    page   
    PAGE compiler option   
    page procedure   
    PAGEWIDTH compiler option   
    parameters
       actual   
       default   
       extensible   
       formal   
       FUNCTION   
       functional   
       hidden   
       list of formal   
       mechanisms   
       procedural   
       PROCEDURE   
       reference   
       relationship of standard level compiler option   
       syntax of formal   
       tables   
       value   
    parsing 16-bit characters   
    PARTIAL_EVAL compiler option   
    partial evaluation of Boolean expressions   
    PASASSM   
    Pascal elements   
    Pascal/V packing algorithm   
    physical files   
    pointer
       dereferencing   
       designator   
    pointer data type coercion   
    pointer data types   
       anyptr   
       class relationship   
       globalanyptr   
       localanyptr   
       long   
       short   
    pointer relational operators   
    pointers   
       address arithmetic   
       constructing values   
       HP3000_16   
    pointer type coercion   
    pointer value
       NIL   
    POP compiler option   
    position function   
    position independent code (PIC)   
    precedence ranking of operators   
    predefine Boolean functions
       haveextension   
    predefined Boolean functions
       haveoptvarparm   
    predefined constants
       maxint   
       minint   
       NIL   
    predefined functions
       addr   
       addtopointer   
       bitsizeof   
       buildpointer   
       sizeof   
    predefined identifiers   
    predefined procedures
       call   
       fcall   
       moving   
    predefined routines
       abs   
       addressing   
       append   
       arctan   
       assert   
       associate   
       baddress   
       binary   
       chr   
       close   
       cmpbytes   
       cos   
       disassociate   
       dispose   
       eof   
       eoln   
       error handling   
       escaping   
       exp   
       get   
       halt   
       hex   
       lastpos   
       linepos   
       ln   
       mark   
       maxpos   
       movebyteswhile   
       moving   
       new   
       octal   
       odd   
       open   
       ord   
       overprint   
       pack   
       page   
       parameter mechanisms   
       position   
       pred   
       prompt   
       put   
       read   
       readdir   
       readln   
       release   
       reset   
       rewrite   
       round   
       routine mechanisms   
       scanuntil   
       scanwhile   
       seek   
       setstrlen   
       sin   
       size functions   
       sqr   
       sqrt   
       str   
       strappend   
       strdelete   
       strinsert   
       strlen   
       strltrim   
       strmax   
       strmove   
       strpos   
       strread   
       strrpt   
       strrtrim   
       strwrite   
       succ   
       system programming extensions   
       trunc   
       unpack   
       waddress   
       write   
       writedir   
       writeln   
    predefine functions
       escapecode   
    predefine procedures
       fast_fill   
       move_fast   
       move_L_to_R   
       move_R_to_L   
    predefine routines
       escape   
    pred function   
    predicate functions   
       odd   
    previous stack pointer   
    printing
       array and record type information   
       notes   
       offsets and statement numbers   
    privileged mode routines, calling and executing   
    procedural parameters   
    procedures   
       allocation   
       append   
       assert   
       associate   
       close   
       conformance   
       deallocation   
       declaration   
       directives   
       disassociate   
       dispose   
       FORWARD directive   
       function calls   
       get   
       halt   
       identifier   
       list of predefined   
       mark   
       movebyteswhile   
       new   
       open   
       overprint   
       pack   
       page   
       program control   
       prompt   
       put   
       read   
       readdir   
       readln   
       recursion   
       release   
       reset   
       rewrite   
       seek   
       setstrlen   
       statement   
       strappend   
       strdelete   
       string   
       strinsert   
       strmove   
       strread   
       strwrite   
       system programming extensions   
       transfer   
       unpack   
       write   
       writedir   
       writeln   
    program block   
    program control procedures   
       assert   
       halt   
    program heading   
    program structure
       block   
       declaration part   
       directive   
       example   
       EXPORT   
       function   
       heading   
       IMPLEMENT   
       IMPORT   
       module   
       procedure   
    prompt   
    prompt procedure   
    PUSH compiler option   
    put procedure   

R
    range checking   
    RANGE compiler option   
    readdir procedure   
    reading a value in strings   
    readln procedure   
    read procedure   
    real data type   
    real literals   
    real numbers
       HP3000_16   
       HP3000_32   
    record
       alignment requirements   
       constant   
       constructor   
       designator   
       printing information   
       selector   
       WITH   
    record data type   
    record fields   
    record variant declaration   
    recursion   
    reference parameters   
    reference type coercion   
    referencing
       data   
       routines   
    referencing routines or data   
    relational operators   
    release procedure   
    releasing the allocation state   
    renaming components   
    REPEAT..UNTIL statement   
    representation type coercion   
    reserved words   
       ANYVAR   
       ARRAY   
       BEGIN..END   
       CASE   
       CONST   
       CRUNCHED   
       definition   
       DO   
       DOWNTO   
       ELSE   
       END   
       EXPORT   
       file   
       GOTO   
       IF   
       IMPLEMENT   
       IMPORT   
       OF   
       OTHERWISE   
       PAC   
       PACKED   
       READONLY   
       REPEAT   
       SET OF   
       STANDARD_LEVEL   
       system programming   
       system programming extension, table of   
       table of   
       THEN   
       TO   
       TYPE   
       UNTIL   
       VAR   
       WHILE   
       WITH   
    reset procedure   
    resetting files   
    restoring compiler option settings   
    restricted set constructor   
    rewrite procedure   
    rewriting files   
    RLFILE compiler option   
    RL file initialization   
    RLINIT compiler option   
    round function   
    routine mechanisms
       call   
       fcall   
       invoking a function   
       invoking a procedure   
    routine options   
       default parameters   
       DEFAULT_PARMS   
       EXTENSIBLE   
       extensible parameters   
       INLINE   
       UNCHECKABLE_ANYVAR   
       UNRESOLVED   
    routine references   
    routines
       predefined   
    routine type   

S
    S300_EXTNAMES compiler option   
    saving compiler option settings   
    scanning source byte strings   
    scanuntil function   
    scanwhile function   
    SEARCH compiler option   
    searching for module definitions   
    search path   
       setting or modifying   
    seek procedure   
    selecting an action   
    selector
       array   
       designator   
       file buffer   
       record   
    separators, definition   
    sequential files   
    SET compiler option   
    set constructor   
    setconvert procedure   
    set data type   
    set operators   
    set relational operators   
    sets
       HP3000_32   
    set size, limitation   
    setstrlen procedure   
    setting column width read by the compiler   
    shared libraries   
    SHLIB_CODE compiler option   
    SHLIB_VERSION compiler option   
    shortint data type   
    side-effects   
    signed integer literal   
    signed subranges   
    simple data types   
       longreal   
       ordinal   
       real   
    simple relational operators   
    sin function   
    size functions   
    sizeof predefined function   
    skipping text   
    SKIP_TEXT compiler option   
    source code
       generating a list of   
    space
       freeing in the heap   
       merging and reuse   
    special symbols, table of   
    SPLINTR compared with SYSINTR   
    SPLINTR compiler option   
    sqr function   
    sqrt function   
    stack pointer   
    STANDARD_LEVEL compiler option   
    standard level compiler option parameters
       HP_MODCAL   
       HP_PASCAL   
       ISO   
    standard level parameters, relationship of   
    standard modules
       stderr   
       stdinput   
       stdoutput   
    standard textfiles   
       input   
       output   
    starting a new page   
    STATEMENT_NUMBER compiler option   
    statements
       assignment   
       BEGIN..END   
       case   
       compound   
       definition of   
       empty   
       FOR..DO   
       GOTO   
       IF..THEN   
       IF..THEN..ELSE   
       procedure   
       REPEAT..UNTIL   
       syntax   
       system programming extensions   
       table of Pascal   
       TRY-RECOVER   
       WHILE..DO   
       WITH   
       WITH..DO   
    static variable   
    stderr standard module   
    stdinput standard module   
    stdoutput standard module   
    STDPASCAL_WARN compiler option   
    stopping a program   
    storage
       allocation   
       deallocation   
    storage type coercion   
    strappend procedure   
    strconvert procedure   
    strdelete procedure   
    str function   
    string assignment
       compatibility   
       table of rules   
    string constructor   
    string data types   
    string functions   
    string literals   
    string procedures   
    string relational operators   
    string routines
       setstrlen   
       str   
       strappend   
       strdelete   
       strinsert   
       strlen   
       strltrim   
       strmax   
       strmove   
       strpos   
       strread   
       strrpt   
       strrtrim   
       strwrite   
    strings
       ANSI definition   
       appending   
       copying characters   
       definition   
       deleting characters   
       HP3000_32   
       initialization   
       inserting characters   
       manipulation   
       reading a value   
       setting length   
       type   
       VAR   
       writing values   
    STRINGTEMPLIMIT compiler option   
    strinsert procedure   
    strlen function   
    strltrim function   
    strmax function   
    strmove procedure   
    strpos function   
    strread procedure   
    strrpt function   
    strrtrim function   
    structural type coercion   
    structured constants   
    structured data types   
       array   
       file   
       packed   
       record   
       set   
       string   
    strwrite procedure   
    sub-integer   
    SUBPROGRAM compiler option   
    subrange data type   
    subranges
       signed   
       unsigned   
    succ function   
    super-integer   
    suppressing warning messages and notes   
    symbols
       basic   
       special, table of   
    SYMDEBUG compiler option   
    syntax
       non-conforming to ANSI/ISO standards   
    syntax level specification   
    SYSINTR compared with SPLINTR   
    SYSINTR compiler option   
    SYSPROG compiler option   
    system-dependent compiler options   
       HP-UX   
       MPE/iX   
    system-independent compiler options   
    system programming compiler options   
    system programming extensions   
       data types   
    system routine, accessing   
    system-wide file   

T
    TABLES compiler option   
    tag field identifier   
    tag fields   
    terminating a program   
    text
       skipping   
    textfiles   
       formatting of output   
       input, output   
       standard   
    TITLE compiler option   
    title specification   
    transfer functions   
       pred   
       round   
       succ   
       trunc   
    transfer procedures   
       pack   
       unpack   
    true, Boolean value   
    trunc function   
    type
       text   
    type coercion   
       ordinal   
       other   
       pointer   
    TYPE_COERCION compiler option   
    type compatibility   
    type definition   
    type identifier   
    types
       integral-types   

U
    UNCHECKABLE_ANYVAR routine option   
    undetected errors   
    unpacked array   
    unpack procedure   
    UNRESOLVED routine option   
    unsigned integer literal   
    unsigned subranges   
    UPPERCASE compiler option   
    uppercase letter differentiation   
    upshifting external names   

V
    value parameters   
    values
       final   
       initial   
    value type coercion   
    variables
       declaration   
       dynamic   
       global   
       local   
       modification of   
       module   
       nonlocal   
       static   
    variant part   
    variants
       records   
       tag fields   
    variants, multiple   
    VAR string   
    VERSION compiler option   
    version number inclusion   
    VOLATILE compiler option   

W
    waddress function   
    WARN compiler option   
    warning messages and notes suppression   
    warnings
       reflected in listing   
    WHILE..DO statement   
    WIDTH compiler option   
    width of compiler listing, specification   
    Wirth, Nicklaus   
    WITH..DO statement   
    WITH statement   
    writedir procedure   
    writeln procedure   
    write procedure   
    writing files   
    writing values in strings   

X
    XREF compiler option   



MPE/iX 5.0 Documentation