C$CALLEDBY
The C$CALLEDBY library routine returns the name of the program that has called the currently running program.
If the calling program does not exist or is not known, then spaces are returned. Spaces are returned also if the currently running program was called through the iscobol.remote.code_prefix.
Syntax:
 CALL "C$CALLEDBY" USING  callingProgram
                   GIVING returnCode
Parameters:
callingProgram
PIC X(n)
Receives the name of the caller.
Return code:
returnCode can be any signed numeric data item and provides additional information:
1
The currently running program has been called by another isCOBOL program.
0
The currently running program is the main program, no other isCOBOL program has called it.
-1
The currently running program has not been called by another isCOBOL program, the caller is unknown
Examples:
Example - Display what program called the current one in the beginning of the program
working-storage section.
77 calling-prg  pic x(256). 
...
procedure division.
main.
  call "c$calledby" using calling-prg
  if calling-prg = spaces
     display message "No program called me"
  else
     display message "I was called by program : " calling-prg
  end-if.