HELPLIB.HLB  —  PASCAL  Statements
  VSI Pascal statements specify actions to be performed and appear
  in executable sections.  They are classified as either simple or
  structured.

  The  simple  statements  are  the  assignment,   empty,   BREAK,
  CONTINUE, EXIT, GOTO, NEXT, RETURN, and routine call.

  The structured statements are the compound,  conditional  (CASE,
  IF-THEN[-ELSE],   SELECT[ONE]),  repetitive  (FOR[-IN],  REPEAT,
  WHILE), and WITH statements.

1  –  Assignment

  An assignment statement uses  an  assignment  operator  (:=)  to
  assign a value to a variable or function identifier.

  Syntax:

     variable-access := expression

  The 'variable-access' is an identifier, array component,  record
  component, pointer dereference, or file buffer.

  The  'expression'  is  a  run-time  expression  whose  type   is
  assignment  compatible with the type of the variable.  The value
  of the expression is the value assigned to the variable.

1.1  –  Examples

    X := 1;      {variable 'X' is assigned the value 1}
    T := A < B;  {value of Boolean expression 'A < B' is assigned to 'T'}
    Vowels := ['A', 'E', 'I', 'O', 'U'];  {set variable 'Vowels' is
                                           assigned the set constructor
                                           ['A', 'E', 'I', 'O', 'U']}

2  –  BREAK

  The BREAK statement immediately transfers control to  the  first
  statement  past  the  end of the FOR, WHILE, or REPEAT statement
  that contains the BREAK statement.  The BREAK statement  appears
  as  a  single  word:   BREAK  is equivalent to a GOTO to a label
  placed just past the end of the closest FOR,  WHILE,  or  REPEAT
  statement.

  Use caution  when  using  the  BREAK  statement  because  future
  additions  to the code may result in the BREAK statement leaving
  a different loop than was originally intended.

  The following example shows the usage of the BREAK statement.

    name := GetInput('Your name?');
    IF ExitKeyPressed THEN BREAK;
    address := GetInput('Your address?');
    IF ExitKeyPressed THEN BREAK;
    Person[Num].Name := name;
    Person[Num].Addr := address;
    Num := SUCC(Num);
  UNTIL Num > 50;

  In the example, a user-defined function GetInput interacts  with
  the  user  and  sets a global Boolean variable ExitKeyPressed if
  the user presses an Exit key.  The  BREAK  statement  exits  the
  loop here, without storing data in the array.

3  –  CASE

  The CASE statement  causes  one  of  several  statements  to  be
  executed.   The  execution  depends  on  the value of an ordinal
  expression called the case selector.

  Syntax:

     CASE case-selector OF
          [[{{case-label-list},... : statement};...]]
          [[ [[;]] OTHERWISE {statement};...]]
          [[;]]
         END

  The 'case-selector' is an expression of an ordinal type.

  The 'case-label-list' is one or more case  labels  of  the  same
  ordinal  type as the case selector, separated by commas.  A case
  label can be a single constant expression, such as 1, or a range
  of expressions, such as 5..10.

  The 'statement' is any statement to be executed depending on the
  values of both the case-selector and the case-label.

  The 'OTHERWISE' clause is executed if  the  value  of  the  case
  selector  does  not  appear  in the case label list.  This is an
  optional clause, but if you omit  it,  the  value  of  the  case
  selector must be equal to one of the case labels.

3.1  –  Examples

     CASE CH OF
         ' ',TAB :  WRITELN( 'Found a space' );
         '0'..'9':  WRITELN( 'Found a digit' );
         'A'..'Z':  WRITELN( 'Found a capital letter' );
         OTHERWISE
                    WRITELN( 'Illegal character' );
     END;

  At run time, the system evaluates the  case  selector  'CH'  and
  executes  the  corresponding statement.  If the value of 'CH' is
  not equal to ' ', '0'..'9' or 'A'..'Z',  the  statement  in  the
  'OTHERWISE' clause is executed.

4  –  Compound

  A compound statement groups a series of statements so that  they
  can  appear  anywhere  that  language  syntax calls for a single
  statement.

  Syntax:

     BEGIN
     {statement};...
     END

  The 'statement' is any VSI  Pascal  statement,  including  other
  compound statements.

5  –  CONTINUE

  The body of a  FOR,  WHILE,  or  REPEAT  loop  can  include  the
  CONTINUE  statement.   The CONTINUE statement is equivalent to a
  GOTO to a label placed at the end of the statements in the  body
  of  the FOR, WHILE, or REPEAT statement.  The CONTINUE statement
  appears as a single word:

   CONTINUE

  In a loop that processes a series of data items, you can use the
  CONTINUE  statement  to  indicate that the rest of the loop does
  not apply to the current  item,  and  that  the  program  should
  continue to the next statement.

  Use caution when using the  CONTINUE  statement  because  future
  additions  to  the  code  may  result  in the CONTINUE statement
  continuing with a different loop than was originally intended.

6  –  Empty Stmt

  The empty statement causes no action to  occur  other  than  the
  advancement of program flow to the next statement.

  To use the empty statement, place a semicolon where the language
  syntax calls for a statement.

7  –  EXIT

  The EXIT statement is identical to the BREAK statement

8  –  FOR

  The FOR statement is a looping statement that repeats  execution
  of  a  statement  according  to the value of a control variable.
  The control variable assumes a value within a specified range or
  set.  A FOR statement has one of the following forms:

     FOR control-variable := initial {TO | DOWNTO} final-value DO
        statement

     FOR control-variable IN set-expression DO
        statement

  The 'control-variable' is the  name  of  a  previously  declared
  variable of an ordinal type.

  The 'initial-value' and 'final-value' are expressions that  form
  a range and whose type is assignment compatible with the type of
  the control variable.

  The 'set-expression' is an expression resulting in  a  value  of
  SET  type.   The  base  type  of  the  set  must  be  assignment
  compatible with the control variable.

  The 'statement' is any VSI Pascal statement that does not change
  the value of the control variable.

  At run time, the initial and final values or the set  expression
  is evaluated before the loop body is executed.

  The 'TO | DOWNTO' directives determine  whether  loop  iteration
  will be incremental or decremental, respectively.

  In the TO form, VSI Pascal checks to see if  the  value  of  the
  control  variable  is less than or equal to the final value.  If
  this condition is met, the control variable takes on  the  value
  of  the  initial  value  for  the  first loop iteration.  During
  iterations, the control variable  increments  according  to  its
  data  type.  Looping ceases when the control variable is greater
  than the final value.

  In the DOWNTO form, VSI Pascal checks to see if the value of the
  control  variable  is  greater than or equal to the final value.
  If this condition is met, the  control  variable  takes  on  the
  value of the initial value for the first loop iteration.  During
  iterations, the control variable  decrements  according  to  its
  data  type.   Looping  ceases  when the control variable is less
  than the final value.

  In the set expression form, VSI Pascal checks to see if the  set
  expression  is not the empty set.  If this condition is met, the
  control variable takes on the value of one of the members of the
  set.  Iterations occur for each member of the set; the selection
  order of members of the set is undefined.  Looping  stops  after
  the loop body executes for each member of the set.

  In both the TO and  the  DOWNTO  forms,  incrementation  of  the
  control  variable  depends  on  its  type.   For example, values
  expressed in type INTEGER increment or decrement in units of  1.
  Values   expressed  in  type  CHAR  increment  or  decrement  in
  accordance with the ASCII collating sequence.

  After normal termination  of  the  FOR  statement,  the  control
  variable  does  not retain a value.  You must assign a new value
  to this variable before you use it elsewhere in the program.  If
  the  FOR  loop  terminates  with  a  GOTO statement, the control
  variable retains the last assigned value.  In this case, you can
  use the variable again without assigning a new value.

8.1  –  Examples

  Example:

      FOR I := 1 TO 10 DO
        FOR J := 1 TO 10 DO
           A[I,J] := 0;

  This example shows how you can nest FOR loops.  For  each  value
  of  I,  the executing program steps through all 10 values of the
  array J and assigns the value 0 to each component.

  Example:

     FOR I IN Set 1 DO
        Set2 := Set2 + [I + 1];

  This example shows a FOR-IN statement.   Set2  is  assigned  the
  successor of each value in Set1.

9  –  GOTO

  The GOTO statement causes an unconditional branch to a statement
  prefixed by a label.

  Syntax:

     GOTO label

  The 'label' is an unsigned decimal integer or symbolic name that
  represents a statement label.

  The GOTO statement  must  be  within  the  scope  of  the  label
  declaration.   A  GOTO  statement  that  is outside a structured
  statement  cannot  jump  to  a  label  within  that   structured
  statement.   A  GOTO  statement within a routine can branch to a
  labeled statement in an enclosing  block  only  if  the  labeled
  statement appears in the block's outermost level.

9.1  –  Examples

     FOR i := 1 TO 10 DO
        BEGIN
        IF Real_Array[i] = 0.0
        THEN
           BEGIN
           Result := 0.0;
           GOTO 10;
           END;
        Result := Result + 1.0/Real_Array[i];
        END;

     10: Invertsum := Result;

  This example shows how to use a GOTO statement to  exit  from  a
  loop.   The  loop  computes  the  sum  of  the  inverses  of the
  components of the variable 'Real_Array'.  If the value of one of
  the  components  is  0.0,  the  sum  is  set to 0.0 and the GOTO
  statement forces an exit from the loop.

10  –  IF_THEN_ELSE

  The IF statement tests  a  Boolean  expression  and  performs  a
  specified  action  if  the result of the test is TRUE.  The ELSE
  clause, when it appears, executes only  if  the  test  condition
  results to FALSE.

  Syntax:

     IF boolean-expression THEN statement1 [[ELSE statement2]]

  The 'boolean-expression' is any Boolean expression.

  The 'statement1' is the statement to be executed if the value of
  the Boolean expression is TRUE.

  The 'statement2' is the statement to be executed if the value of
  the Boolean expression is FALSE.

  VSI Pascal may not always evalutate all the terms of  a  Boolean
  expression if it can evaluate the entire expression based on the
  value of one term.  Either do not write  code  that  depends  on
  actual  evalution  (or evaluation order) of Boolean expressions,
  or use the AND_THEN and  OR_ELSE  operators  for  a  predictable
  order of evaluation.

10.1  –  Examples

     IF x > 10 THEN y := 4           IF x > 10 THEN BEGIN y := 4;
               ELSE y := 5;                               z := 5;
                                                    END
                                               ELSE y := 5;

  The ELSE clause always modifies the closest IF-THEN statement.

  Use caution to avoid logic errors in nested IF statements, as in
  the following:

     IF A = 1 THEN    {First IF}
        IF B<>1 THEN  {Second IF}
           C := 1
     ELSE             {Appears to modify first IF}
        C := 0;       {Actually modifies second IF}

11  –  NEXT

  The NEXT statement is identical to the CONTINUE statement.

12  –  REPEAT

  The REPEAT statement is a looping statement and executes one  or
  more statements until a specified condition is true.

  Syntax:

     REPEAT
        {statement};...
     UNTIL expression

  The 'statement' is any VSI Pascal statement.

  The 'expression' is any Boolean expression.

  VSI Pascal always executes a REPEAT statement for one iteration;
  iterations  continue as long as the Boolean expression is FALSE.
  When specifying more than one statement as the loop  body  to  a
  REPEAT  statement,  do not enclose the statements with the BEGIN
  and END reserved words; multiple statements  are  legal  in  the
  REPEAT loop body.

12.1  –  Examples

     REPEAT
        READ (x);
        IF (x IN ['0'..'9'])
        THEN
           BEGIN
           Digit_count := Digit_count + 1;
           Digit_sum := Digit_sum + ORD (x) - ORD ('0');
           END
        ELSE
           Char_count := Char_count + 1;
     UNTIL EOLN (INPUT);

  Assume that the variable 'x' is of type CHAR and  the  variables
  'Digit_count',  'Digit_sum',  and  'Char_count' denote integers.
  The example reads a character (x).  If the value  of  'x'  is  a
  digit,  the count of digits is incremented by one and the sum of
  digits is increased by the value of 'x', as computed by the  ORD
  function.   If  the  value  of  'x' is not a digit, the variable
  'Char_count' is incremented by one.  The REPEAT  loop  continues
  processing characters until it reaches an end-of-line condition.

13  –  RETURN

  The RETURN statement passes control back  to  the  caller  of  a
  PROCEDURE,   FUNCTION,  PROGRAM,  or  module  initialization  or
  finalization section.  A RETURN statement  is  equivalent  to  a
  GOTO to a label placed just before the END of the body, and in a
  PROGRAM, has the effect of stopping the program

  Syntax:

  RETURN [ return-value ]

  Inside a FUNCTION, return-value specifies an  ending  value  for
  the  FUNCTION.   If  no return-value is provided, the last value
  assigned to the function identifier  is  used  as  the  function
  result.   The  return-value  type  and function type must be the
  same.

  Inside a PROGRAM, the return-value specifies an ending value for
  the  PROGRAM.   If you do not provide a return-value, VSI Pascal
  uses the value 1 on OpenVMS systems.

  Inside a PROCEDURE, module  initialization  section,  or  module
  finalization section, VSI Pascal generates an error.

13.1  –  Example

  FUNCTION FindFirst(StartingPoint: INTEGER) : INTEGER;
    VAR i: INTEGER;
      BEGIN
        FOR i := StartingPoint TO MaximumNumber DO
          BEGIN
          IF Data[i] = Suitable THEN
            BEGIN
            AttributesOfDesiredData = Attributes[i];
            Subscript := i;
            RETURN i;
            END;
          END;
      END;

  The example  shows  the  usage  of  RETURN  ststement.   In  the
  example, a function searches through the array called "Data" for
  an element that matches  "Suitable".   When  it  finds  one,  it
  assigns  values  to  two global variables and executes a RETURN.
  Omitting the RETURN statement would make the  function  continue
  processing; it would assign values for the last suitable element
  instead of the first.

14  –  Routine Call

  A routine call executes  all  statements  in  the  body  of  the
  declared  routine.   You  must  declare a routine before you can
  call it.  You can call routines in the executable section  of  a
  program or in the body of another routine.

  When the routine finishes executing, control returns to the next
  executable  statement  in  the  calling  block  that follows the
  routine call.

  Syntax:

     routine-identifier [[ ({actual-parameter-list},...) ]]

  The 'routine-identifier' is the name of a procedure or function.

  The 'actual-parameter-list' is one or more run-time  expressions
  of  an appropriate type, or the name of a procedure or function.
  The appropriate type is determined by the  corresponding  formal
  parameter.

  Actual parameters have the following syntax:

      ({ [[mechanism-specifier]] procedure-identifier
         [[mechanism-specifier]] function-identifier
         [[mechanism-specifier]] expression
         type-identifier
         write-list-element },...)

  The 'mechanism-specifier' is any one of the foreign specifiers.

  The  'procedure-identifier'  is  the  name  of   a   predeclared
  procedure.

  The 'function-identifier' is the name of a predeclared function.

  The 'expression' is any compile-time or run-time expression.

  The 'type-identifier' is a predeclared identifier of any type.

  The 'write-list-element' has the format:

     expression[[:expression[[:expression]]]]

  Example:
     Tollbooth (Change, 0.25, Lane[1]);

  This statement calls the procedure 'Tollbooth', and  passes  the
  variable  'Change',  the  real  constant  '0.25',  and the first
  component of the array 'Lane' as actual parameters.

  Example:
     Taxes (Rate*Income, 'Pay');

  This statement calls the procedure 'Taxes', with the  expression
  'Rate*Income'   and   the   string   constant  'Pay'  as  actual
  parameters.

15  –  SELECT[ONE]

  The SELECT statement  causes  zero,  one,  or  more  of  several
  statements  to be executed.  The SELECTONE statement causes zero
  or one statements to be executed.  The execution depends on  the
  value of an ordinal expression called the select selector.

  The SELECT and SELECTONE statements  look  much  like  the  CASE
  statement  except  for  one  very powerful feature.  Namely, the
  labels of a  SELECT  or  SELECTONE  statement  can  be  run-time
  expressions  as  opposed to the CASE statement which only allows
  constant expressions.

  Syntax:

     SELECT select-selector OF
            [[{{select-label-list},...: statement};...]]
            [[ [[OTHERWISE {statement};...]]
               [[ALWAYS {statement};...]] ]]
            [[;]]
        END

     SELECTONE select-selector OF
            [[{{select-label-list},...: statement};...]]
            [[ OTHERWISE {statement};... ]]
            [[;]]
        END

  The 'select-selector' is an expression of an ordinal type.

  The 'select-label-list' is one or more select labels of the same
  ordinal  type  as  the  select selector, separated by commas.  A
  select label can be a single expression, such as 1, or  a  range
  of   expressions,   such   as   5..10.   The  expressions  in  a
  'select-label-list' can be full run-time expressions.

  When two expressions are provided as a lower  and  upper  bound,
  they  must  be  of  the same ordinal type.  There is no check to
  ensure that the lower bound expression is less than or equal  to
  the  upper  bound  expression.  If that occurs then there are no
  values of the select-selector that can be in the range.

  The 'statement' is any statement to be executed depending on the
  values of both the select-selector and the select-label.

  The  SELECT  statement  checks  to  see  if  the  value  of  the
  select-selector  is  contained in the select-label-list.  If so,
  then   the   corresponding   statement   is    executed.     The
  select-label-lists  are  checked  in the same lexical order that
  they appear in the source file.  The same value  can  appear  in
  more  than  one select-label-list.  All corresponding statements
  to select-label-lists are executed if the value is contained  in
  the  select-label-list.   By  contrast,  the SELECTONE statement
  stops processing after it  executes  the  first  statement  that
  corresponds   to   a   select-label-list   that   contains   the
  select-selector value.

  The optional OTHERWISE and ALWAYS clauses can appear  in  either
  order.   The  ALWAYS  clause  is always executed.  The OTHERWISE
  clause is executed only if none of the prior statements  (except
  for an optional ALWAYS statement) have been executed.

  The syntax for the SELECTONE statement is almost  identical  but
  does not provide for an ALWAYS clause.

15.1  –  Examples

  While the SELECT/SELECTONE statements can be used similar to the
  CASE statement.  For example,

     SELECT expression OF
      1: WRITELN('ONE');
      2: WRITELN('TWO');
      OTHERWISE WRITELN('not ONE or TWO')
      END

  a more subtle (and powerful)  form  uses  the  Boolean  constant
  'TRUE' as the select-selector.  For example,

     SELECTONE True OF
      expression < 10: WRITELN('Value is small');
      expression < 100: WRITELN('Value is medium');
      expression < 1000: WRITELN('Value is big');
      OTHERWISE WRITELN('Value is too big');
      END

     SELECTONE True OF
      expression = "AAA": writeln('String is AAA');
      expression = "BBB": writeln('String is BBB');
      expression = "CCC": writeln('String is CCC');
      OTHERWISE writeln('unknown string');
      END

     FOR i := 1 TO 10 DO
       SELECT True OF
        ODD(i): WRITELN('value ',i:1,' is odd');
        (i MOD 3) = 0:
                WRITELN('value ',i:1,' is also a multiple of 3');
        END;

16  –  WHILE

  The WHILE statement is a loop that executes a statement while  a
  specified condition is true.

  Syntax:

     WHILE expression DO
        statement

  The 'expression' is any Boolean expression.

  The 'statement' is any VSI Pascal statement.

  VSI Pascal checks the value of  the  Boolean  expression  before
  executing the loop body for the first time; if the expression is
  FALSE, the loop body is not executed.  If the initial  value  is
  TRUE,  loop  iterations  continue  until the condition is FALSE.
  When specifying more than one statement as the loop  body  to  a
  WHILE  statement,  enclose the statements with the BEGIN and END
  reserved words, since the syntax calls for a single statement to
  follow  the  DO  reserved  word.   If  you do not use a compound
  statement for the loop  body,  VSI  Pascal  executes  the  first
  statement following the DO reserved word as the loop body.

16.1  –  Examples

     WHILE NOT EOLN (INPUT) DO
        BEGIN
        READ (x);
        IF NOT (x IN ['A'..'Z', 'a'..'z', '0'..'9'])
        THEN
           Err := Err + 1;
        END;

  This example reads an input character (x) from the current line.
  If  the  character  is  not  a digit or letter, the error count,
  'Err', is incremented by  one.   The  loop  terminates  when  an
  end-of-line on the INPUT is reached.

17  –  WITH

  The  WITH  statement  provides  an  abbreviated   notation   for
  references  to  the fields of a record variable or to the formal
  discriminants of a discriminated schema type.

  Syntax:

     WITH {record-variable | schema-variable},... DO
        statement

  The 'record-variable' is the name of the record  variable  being
  referenced.

  The 'schema-variable' is the name of the schema  variable  being
  referenced  whose  type  is  a  discriminated schema type.  This
  underlying type of the schema can be a record.

  The 'statement' is any VSI Pascal statement.

  The WITH statement allows you to refer to the fields of a record
  or  to  an formal discriminant of a schema by their names alone,
  rather    than     by     the     record.field-identifier     or
  schema-variable.formal-discriminant syntax.  In effect, the WITH
  statement  opens  the  scope  so  that   references   to   field
  identifiers  or  to  formal discriminants alone are unambiguous.
  When you access a variable using a WITH statement, the reference
  syntax lasts only throughout the execution of the statement.

  If you are specifying nested records, their variable names  must
  appear in the order in which they were nested in the record type
  definition.  If you are working with record and schema variables
  that  are  not  nested,  you  can  specify variable names in any
  order.  If you specify record or schema  variables  whose  field
  names  or  formal  discriminants  conflict with one another, VSI
  Pascal uses the last record or schema in the comma list.

17.1  –  Examples

  Example:

     WITH Cat, Dog DO
        Bills := Bills + Cat_vet + Dog_vet;

  where 'Cat' and 'Dog' are records and 'Cat_vet' is  a  field  of
  'Cat' and 'Dog_vet' is a field of 'Dog'.

  Example:

     VAR
        x : STRING( 10 );
        y : STRING( 15 );

     WITH x, y DO
        WRITELN( CAPACITY );

  VSI Pascal uses the last  schema  variable  specified,  y.   The
  WRITELN statement prints y.CAPACITY.
Close Help