SYNCHRONIZED Clause


  • COBOL allocates contiguous memory for the variables declared while the program starts execution. The variable's memory allocation starts at respective boundaries (half-word boundaries - 4 bytes) to increase the computation efficiency of the program.
  • Due to the variable allocation at the word boundaries, some bytes are unused between the boundary start and the previous allocation ending. These unused bytes are called Slack bytes.
  • SYNCHRONIZED clause allocates the variables at their respective natural memory boundaries (immediately after the previous allocation ends). It removes the slack bytes.

Syntax -

data-item   PIC data-type(length) [SYNCHRONIZED|SYNC [LEFT|RIGHT]]
Note! All statements coded in [ ] are optional.

Parameters -

  • data-item - Name of the variable declared.
  • PIC data-type(length) - Specifies the type and size of the data item.
  • LEFT - Optional. It specifies left alignment. It is used for alphabetic and alphanumeric items.
  • RIGHT - Optional. It specifies right alignment. It is used for numeric items. If neither is coded, RIGHT is the default.

Slack Bytes -


The memory bytes that are left unused between the memory allocations are called slack bytes. There are two types of slack bytes -

  • Slack bytes within records
  • Slack bytes between records

Slack bytes within records -


Slack bytes (unused character positions) are added before each synchronized item in the records. For Example -

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
   05 STUDENT-NAME     PIC X(12).
   05 STUDENT-GRADE    PIC 9(02).
   05 STUDENT-CLASS    PIC X(03).

After the compiler inserts the slack bytes, the declaration is modified. For instance, after STUDENT-NO, the next item STUDENT-NAME starts from the boundary. Similarly, for STUDENT-GRADER, the STUDENT-CLASS starts from the boundary after the insertion of slack bytes. The declaration after slack bytes is -

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
  [05 SLACK-BYTES      PIC XX.  INSERTED BY COMPILER]
   05 STUDENT-NAME     PIC X(12).
   05 STUDENT-GRADE    PIC 9(02).
  [05 SLACK-BYTES      PIC XX.  INSERTED BY COMPILER]
   05 STUDENT-CLASS    PIC X(03).

The below diagram represents the memory allocation along with slack bytes -

Four slack bytes are inserted if we do not use the SYNC clause. The variables (followed by slack bytes) should declare with SYNC clause to avoid the slack bytes as shown below -

01 STUDENT.
   05 STUDENT-NO       PIC 9(02).
   05 STUDENT-NAME     PIC X(12) SYNC.
   05 STUDENT-GRADE    PIC 9(02).
   05 STUDENT-CLASS    PIC X(03) SYNC.

The diagram below represents the same allocation after introducing the SYNC clause. There will be no slack bytes anymore -