The CallableProgram type is used to create a .Net type that can be used with the CALL verb.
            
            Below is an example the type that for a program called MYPROGRAM.  
            
            The type also implements ICancelProgramCallback interface so it can handle being CANCELed.
            
Inheritance Hierarchy
MicroFocus.COBOL.RuntimeServicesCallableProgram
Namespace: MicroFocus.COBOL.RuntimeServices
Assembly: MicroFocus.COBOL.RuntimeServices (in MicroFocus.COBOL.RuntimeServices.dll) Version: 1.2.3.4
Syntax
The CallableProgram type exposes the following members.
Constructors
| Name | Description | |
|---|---|---|
|  | CallableProgram | 
Examples
COBOL
using System;
[assembly: MicroFocus.COBOL.Info.Callable()]
namespace MicroFocus.COBOL.Runtime
{
    [MicroFocus.COBOL.Info.Callable()]
    public class MyProgramType : MicroFocus.COBOL.RuntimeServices.CallableProgram,
                 MicroFocus.COBOL.RuntimeServices.CallableProgram.ICancelProgramCallback
    {
        private int counter;
        public MyProgramType()
        {
            init();
        }
        private void init()
        {
            this.counter = 42;
        }
        [MicroFocus.COBOL.Info.Callable()]
        public int MYPROGRAM()
        {
            return counter++;
        }
        public void OnCancelProgram(bool OnStop)
        {
            Console.WriteLine("OnCancelProgram for MYPROGRAM -> "+OnStop);
            init();
        }
    }
}COBOL
WORKING-STORAGE SECTION. CALL "MYPROGRAM" DISPLAY "MYPROGRAM: Return-Code: " return-code CALL "MYPROGRAM" DISPLAY "MYPROGRAM: Return-Code: " return-code CANCEL "MYPROGRAM" CALL "MYPROGRAM" DISPLAY "MYPROGRAM: Return-Code: " return-code
See Also