HLLPIPI examples

Following is an example of a C subroutine called by ASMPIPI:
/*Module/File Name:  EDCPIPI  */
 /**********************************************************/
 /*                                                        */
 /* HLLPIPI is called by an assembler program, ASMPIPI.    */
 /* ASMPIPI uses the LE preinitialized program             */
 /* subroutine call interface. HLLPIPI can be written      */
 /* in COBOL, C, or PL/I.                                  */
 /*                                                        */
 /**********************************************************/
#include <stdio.h>
#include <string.h>
#include <time.h>
#pragma linkage(HLLPIPI, fetchable)
HLLPIPI ()
{
 printf ( "C subroutine beginning\n" );
 printf ( "Called using LE PreInit call\n" );
 printf ( "Subroutine interface.\n" );
 printf ( "C subroutine returns to caller\n" );
}
Following is an example of a COBOL program called by ASMPIPI:
CBL LIB,QUOTE
      *Module/File Name: IGZTPIPI
      ***********************************************************
      *                                                         *
      * HLLPIPI is called by an assembler program, ASMPIPI.     *
      * ASMPIPI uses the LE preinitialized program              *
      * subroutine call interface. HLLPIPI can be written       *
      * in COBOL, C, or PL/I.                                   *
      *                                                         *
      ***********************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. HLLPIPI.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
           DISPLAY "COBOL subprogram beginning".
           DISPLAY "Called using LE Preinitialization ".
           DISPLAY "Call subroutine interface.".
           DISPLAY "COBOL subprogram returns to caller.".

           GOBACK.
Following is an example of a routine called by ASMPIPI:
 /*Module/File Name:  IBMPIPI                              */
 /**********************************************************/
 /*                                                        */
 /* HLLPIPI is called by an assembler program, ASMPIPI.    */
 /* ASMPIPI uses the LE preinitialized program             */
 /* subroutine call interface. HLLPIPI can be written      */
 /* in COBOL, C, or PL/I.                                  */
 /*                                                        */
 /**********************************************************/
  HLLPIPI: PROC OPTIONS(FETCHABLE);
           DCL RESULT FIXED BIN(31,0) INIT(0);
           PUT SKIP LIST
               ('HLLPIPI  : PLI subroutine beginning.');
           PUT SKIP LIST
               ('HLLPIPI  : Called LE PIPI Call ');
           PUT SKIP LIST
               ('HLLPIPI  : Subroutine interface.   ');
           PUT SKIP LIST
               ('HLLPIPI  : PLI program returns to caller.');
           RETURN;
  END HLLPIPI;