4

I am using OpenCOBOLIDE and trying to just simply call a subroutine. I am following along in a TutorialPoint document. I followed all the instructions but cannot seem to figure out why when I call the subroutine it still cannot find the module I am trying to link to.

Here is my main file:

IDENTIFICATION DIVISION.
   PROGRAM-ID. MAIN.

   DATA DIVISION.
    WORKING-STORAGE SECTION.
       01 WS-STUDENT-ID PIC 9(4) VALUE 1000.
       01 WS-STUDENT-NAME PIC A(15) VALUE 'Tim'.

   PROCEDURE DIVISION.
   CALL 'UTIL' USING WS-STUDENT-ID, WS-STUDENT-NAME.
   DISPLAY 'Student Id : ' WS-STUDENT-ID
   DISPLAY 'Student Name : ' WS-STUDENT-NAME
   STOP RUN.

And here is my subroutine:

 IDENTIFICATION DIVISION.
   PROGRAM-ID. UTIL.

   DATA DIVISION.
    LINKAGE SECTION.
       01 LS-STUDENT-ID PIC 9(4).
       01 LS-STUDENT-NAME PIC A(15).

   PROCEDURE DIVISION USING LS-STUDENT-ID, LS-STUDENT-NAME.
       DISPLAY 'In Called Program'.
       MOVE 1111 TO LS-STUDENT-ID.
   EXIT PROGRAM.

I am using OpenCobolIDE-4.6.5 if that helps.

The message I get is:

MAIN.cbl:16: libcob: Cannot find module 'UTIL'
Bill Woodger
  • 12,968
  • 4
  • 38
  • 47

2 Answers2

2

If you look at the COBOL option in the menu-bar at the top of the screen select Program type you'll see two options: Executable; Module.

For the program which is started from the OS, your MAIN, you need that to be set to Executable. For the CALLed program, UTIL, you need that to be set to Module.

You should also try to install GnuCOBOL, which is the new name for OpenCOBOL. GnuCOBOL is actively maintained. The GnuCOBOL site is currently at SourceForge.Net. There is a recent discussion in the Help getting started as to exactly how to do that (for Ubuntu, anyway, if you are using something more different, post a question and you'll get assistance).

Disclosure: I am a Moderator there.

You should be aware that the concept of "main" does not actually exist in COBOL itself, not in the way of other languages you may know. Exactly how the initial program operates is down to implementation and operating system.

On Linux/Unix/Windows the initial program is compiled differently, so it is more like a "main". On an IBM Mainframe it is not compiled differently.

Also note that a subroutine can CALL another subroutine. You would need to compile both as Module in your case. It is not COBOL dictating that, but the OS and the implementation.

If learning COBOL, be modern about it. In the PROCEDURE DIVISION do not attach a full-stop/period to a line of code, and only use them where they are necessary, not where they are optional. In earlier COBOL Standards the full-stop/period was the only scope-terminator available, and for backwards-compatibility it still acts as a "super-scope-terminator" which is usually not what you want, and if it were to be what you want, it is bad practice as any other reader would consider it an error and wonder what you had really intended.

A full-stop/period is needed: to terminate the PROCEDURE DIVISION statement; to terminate a paragraph or SECTION label; to terminate a paragraph or SECTION itself; to terminate a program.

If using a COPY or REPLACE compiler-directive, you also need to terminate those with a full-stop/period.

Your subroutine does not contain a GOBACK, RETURN or EXIT PROGRAM. Even if that were to work, it would be non-Standard, non-portable and would not be a good way to learn COBOL.

In the real-world of COBOL programming you won't/may never find a PIC A used. It is considered of little benefit, as all it does is prevent you using that field as a source and a numeric field as a target in the same statement. Using a PIC X instead of PIC A is what you will normally see, so you may as well start now (despite what any tutorial may say).

That's an opinion, and you've no need to follow that advice, but in practice that is the way it is.

Using commas (or any other non-relevant separator) in COBOL statements only clouds a program. They have no genuine value. This is valid:

PROCEDURE DIVISION USING LS-STUDENT-ID, , , , , LS-STUDENT-NAME.

So what would be the point?

There is no benefit in defining a field as numeric simply because it contains a number. You are never going to do a calculation with the student-id, so it is much better for it to be PIC X not PIC 9.

Bill Woodger
  • 12,968
  • 4
  • 38
  • 47
1

independantly of Bill's excellent remarks, I did face the same problem with OpenCobolIDE today. And found a solution.

You have to parameter the paths of the .dll created so that the caller programm can find the called module. When you compile [F8] your module, you have a message that tells you where the dll has gone :

Compilation succeeded (output: C:\Users\Mariah Flaim\bin\MyModule.dll)

Now, you have to go to the parameters [F2], to the compiler tab, and add a link to this path in the "Library path" list. And, how miracle, the call happens!!!

A very simple example, just to try, I've made work after this manoeuver, starting from their templates(would need more work to be clean, but it works).

Calling program :

   IDENTIFICATION DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   PROGRAM-ID. YOUR-PROGRAM-NAME.
   ENVIRONMENT DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   CONFIGURATION SECTION.
  *-----------------------
   INPUT-OUTPUT SECTION.
  *-----------------------
   DATA DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   FILE SECTION.
  *-----------------------
   WORKING-STORAGE SECTION.
   01 PARAMETRES.
       02 PA-RETURN-CODE PIC 99 VALUE 0.
  *-----------------------
   PROCEDURE DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   MAIN-PROCEDURE.
  **
  * The main procedure of the program
  **
        CALL "MYMODULE"
        USING PARAMETRES
        DISPLAY "Hello world"
        STOP RUN.
  ** add other procedures here
   END PROGRAM YOUR-PROGRAM-NAME.

Called Module :

   IDENTIFICATION DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   PROGRAM-ID. MYMODULE.
   ENVIRONMENT DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   CONFIGURATION SECTION.
  *-----------------------
   INPUT-OUTPUT SECTION.
  *-----------------------
   DATA DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   FILE SECTION.
  *-----------------------
   WORKING-STORAGE SECTION.
  *-----------------------
   LINKAGE SECTION.
  **-*-*-*-*-*-*-*-*-*-*-*-*-*
   01 PARAMETRES.
       02 PA-RETURN-CODE PIC 99 VALUE 0.
   PROCEDURE DIVISION USING PARAMETRES.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   MAIN-PROCEDURE.
  **
  * The main procedure of the program
  **
    DISPLAY "Glu"
    MOVE 0 TO PA-RETURN-CODE
    GOBACK.
  ** add other procedures here
   END PROGRAM MYMODULE.

Output :

Glu
Hello world
gazzz0x2z
  • 326
  • 2
  • 12