Menu

unallocated memory

GnuCOBOL
2023-10-10
2024-03-12
  • Jack Tearle

    Jack Tearle - 2023-10-10

    I wrote the following programs to generate and erase pop-up windows for MicroFocus cobol 4.1 after testing, I thought about running with GnuCOBOL.

    I compiled the programs with both version 3.1.2- and 4.0-early-dev.0. Both versions compiled without error.
    But running, both gave "attempt to reference unallocated memory (signal SIGSEGV).

           IDENTIFICATION DIVISION.
           PROGRAM-ID. TESTBOX.
           ENVIRONMENT DIVISION.
           INPUT-OUTPUT SECTION.
           FILE-CONTROL.
           DATA DIVISION.
           FILE SECTION.
           WORKING-STORAGE SECTION.
           01  lk-data.
              03  lk-line   pic 99.
              03  lk-col    pic 99.
              03  lk-width  pic 99. 
              03  lk-height pic 99.
              03  lk-title  pic x(78).
              03  lk-erase  pic x.
           PROCEDURE DIVISION.
           SOJ.
              display 'enter upper row'.
              accept lk-line  
              display 'enter upper left coll'.
              accept lk-col .
              display 'enter width '
              accept lk-width
              display 'enter height'
              accept lk-height.
              display 'enter write or erase'
              accept lk-erase.
              move 'this box' to lk-title.
    
              call 'box' using lk-data.
              display "enter erase"
              accept lk-erase.
              call 'box' using lk-data.
              stop run.
    

    and

           IDENTIFICATION DIVISION.
           PROGRAM-ID. BOX.
           AUTHOR J. TEARLE.
           DATE-WRITTEN. OCT 2023.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
          *
           01  box.
           02  top-left-corner      pic x value '�'.
               02  top-right-corner     pic x value '�'.
           02  end-col              pic x value '�'.
           02  horiz-line           pic x(78) value all '�'.
           02  bottom-left-corner   pic x value '�'.
               02  bottom-right-corner  pic x value '�'.
               02  box-middle           pic x(78) value spaces.
           01  box-line                 pic x(78).
           01  blank-line               pic x(78).
           01  curr-line                pic 99.
           01  title-width              pic 99.
           01  width2                   pic 99.
           01  height                   pic 99.
           LINKAGE SECTION.
           01  lk-data.
              03  lk-line               pic 99.
              03  lk-col                pic 99.
              03  lk-width              pic 99.
              03  lk-height             pic 99.
              03  lk-title              pic x(78).
              03  lk-erase              pic x.
    
           PROCEDURE DIVISION using lk-data .
           SOJ.
               if lk-erase = "E" 
                  perform erase-box
                  exit program.
               move lk-line to curr-line.
               add 2 lk-width giving width2.
               string top-left-corner horiz-line(1:lk-width)
                      top-right-corner 
                   delimited by size into box-line.
               display box-line(1:width2) at line curr-line col lk-col.
               subtract 1 from lk-width giving title-width.
               string end-col lk-title(1:lk-width) end-col 
                     delimited by size into box-line.
               add 1 to curr-line.
               display box-line(1:width2) at line curr-line col lk-col.
               string end-col horiz-line(1:lk-width) end-col 
                   delimited by size into box-line.
               add 1 to curr-line.
                display box-line(1:width2) at line curr-line col lk-col.
               add 1 to curr-line. 
               subtract 3 from lk-height giving height.
               perform disp-box height times
               string  bottom-left-corner 
                       horiz-line(1:lk-width) bottom-right-corner
                       delimited by size into box-line.
               display box-line(1:width2) 
                    at line curr-line col lk-col.
               exit program.
           disp-box.
               string  end-col box-middle(1:lk-width) end-col 
                delimited by size into box-line
               display box-line(1:width2) at line curr-line col lk-col.
               add 1 to curr-line.
           erase-box.
               move lk-line to curr-line.
               add 2 lk-width giving width2.
               perform disp-blank lk-height times.
           disp-blank.
               display blank-line(1:width2) at line curr-line col lk-col.
               add 1 to curr-line.
    
     

    Last edit: Simon Sobisch 2023-12-31
    • Eugenio Di Lorenzo

      Hi,
      following code works fine.
      I changed call 'box' ... to call 'BOX' ...
      I added two END PROGRAM

              >>SOURCE FREE
      IDENTIFICATION DIVISION.
      PROGRAM-ID. TESTBOX.
      ENVIRONMENT DIVISION.
      INPUT-OUTPUT SECTION.
      FILE-CONTROL.
      DATA DIVISION.
      FILE SECTION.
      WORKING-STORAGE SECTION.
      01 lk-data.
        03 lk-line    pic 99.
        03 lk-col     pic 99.
        03 lk-width   pic 99.
        03 lk-height  pic 99.
        03 lk-title   pic x(78).
        03 lk-erase   pic x.
      PROCEDURE DIVISION.
      SOJ.
        display 'enter upper row'.
        accept lk-line
        display 'enter upper left coll'.
        accept lk-col .
        display 'enter width '
        accept lk-width
        display 'enter height'
        accept lk-height.
        display 'enter write or erase'
        accept lk-erase.
        move 'this box' to lk-title.
      
        call 'BOX' using lk-data.
        display "enter erase"
        accept lk-erase.
        call 'BOX' using lk-data.
        stop run.
      
      
        IDENTIFICATION DIVISION.
        PROGRAM-ID. BOX.
        AUTHOR J. TEARLE.
        DATE-WRITTEN. OCT 2023.
        DATA DIVISION.
        WORKING-STORAGE SECTION.
      
         01  box.
             02  top-left-corner      pic x value '+'.
             02  top-right-corner     pic x value '+'.
             02  end-col              pic x value '|'.
             02  horiz-line           pic x(78) value all '-'.
             02  bottom-left-corner   pic x value '+'.
             02  bottom-right-corner  pic x value '+'.
             02  box-middle           pic x(78) value spaces.
         01  box-line                 pic x(78).
         01  blank-line               pic x(78).
         01  curr-line                pic 99.
         01  title-width              pic 99.
         01  width2                   pic 99.
         01  height                   pic 99.
      
         LINKAGE SECTION.
         01  lk-data.
            03  lk-line               pic 99.
            03  lk-col                pic 99.
            03  lk-width              pic 99.
            03  lk-height             pic 99.
            03  lk-title              pic x(78).
            03  lk-erase              pic x.
      
         PROCEDURE DIVISION using lk-data .
         SOJ.
             if lk-erase = "E" 
                perform erase-box
                exit program.
      
             move lk-line to curr-line.
             add 2 lk-width giving width2.
             string top-left-corner horiz-line(1:lk-width) top-right-corner delimited by size into box-line.
             display box-line(1:width2) at line curr-line col lk-col.
      
             subtract 1 from lk-width giving title-width.
             string end-col lk-title(1:lk-width) end-col delimited by size into box-line.
             add 1 to curr-line.
             display box-line(1:width2) at line curr-line col lk-col.
      
             string end-col horiz-line(1:lk-width) end-col delimited by size into box-line.
             add 1 to curr-line.
             display box-line(1:width2) at line curr-line col lk-col.
      
             add 1 to curr-line. 
             subtract 3 from lk-height giving height.
             perform disp-box height times
             string  bottom-left-corner horiz-line(1:lk-width) bottom-right-corner delimited by size into box-line.
             display box-line(1:width2) at line curr-line col lk-col.
      
             exit program.
      
         disp-box.
             string  end-col box-middle(1:lk-width) end-col delimited by size into box-line
             display box-line(1:width2) at line curr-line col lk-col.
             add 1 to curr-line.
      
         erase-box.
             move lk-line to curr-line.
             add 2 lk-width giving width2.
             perform disp-blank lk-height times.
      
         disp-blank.
             display blank-line(1:width2) at line curr-line col lk-col.
             add 1 to curr-line.
      END PROGRAM BOX.
      
      END PROGRAM TESTBOX.
      
       
  • Jack Tearle

    Jack Tearle - 2023-10-11

    I have tried the changes you made, and still have the same problem. I am using Linux Mint, current version.

     
    • Eugenio Di Lorenzo

      Sorry, I also changed the graphic symbols under 01 boxfield .
      Would you try downloading and compiling just my source code ?

      I also suggest to delete the AUTHOR J. TEARLE. statement.
      It contains two dots ...

      I use GnuCOBOL 3.2 on Windows 10.
      Attached a screenshot of the output.

       

      Last edit: Eugenio Di Lorenzo 2023-10-11
  • Jack Tearle

    Jack Tearle - 2023-10-11

    Still the same problem.

     
    • Simon Sobisch

      Simon Sobisch - 2023-10-11

      So you:

      • used the version from Eugenio
      • used GnuCOBOL 3.2
      • still get an abort?


      What is the command line you use for compiling?

       

      Last edit: Simon Sobisch 2023-10-11
  • Jack Tearle

    Jack Tearle - 2023-10-12

    Simon, I only changed the source code to match Eugenio. I still used 3.1.2 and 4.0
    cobc -x testbox.cbl
    cobc box.cbl

     
    • Eugenio Di Lorenzo

      Hi Jack, there is no need to execute cobc twice.
      In my sample we have only one source file testbox.cob where the source code of program BOX is inside the source code of program TESTBOX , both in one same sourcefile testbox.cob
      Plese download my code , it is just one sourcefile and compile both programs with just one execution: cobc -x testbox.cob

       
      • Mickey White

        Mickey White - 2023-10-12

        I wonder if he needs to remove/delete the current box. object file first? It may not matter if the combined has box as static?

         
    • Simon Sobisch

      Simon Sobisch - 2023-12-31

      Just a follow-up: I've tested this with GC 2.2 as Ubuntu system package and both GC 3.1.2 and 3.2 (unpatched) build manually on the same machine - no abort.

      What I've did was

      • using the original version (I've mod-edited the split into two sources in)
      • changed box.cbl to have PROGRAM-ID. box. (lower-case)
      • compiled and run with cobc -xj testbox.cbl box.cbl

      I do get a running program without an abort. The actual box doesn't work, but that's mostly because the encoded box VALUEs got broken by pasting it here, @kitamanswinner maybe you can change those to be in x'AB' format with the matching hex values and note where the program was running before (same Linux Mint?).

      What values do you enter for the ACCEPTs?

      So in general - if this creates this error for you, it seems to be something system-specific and GnuCOBOL may be able to do something about that.
      To check - could you please build the last release with debug information and run it again?

      wget https://ftp.gnu.org/gnu/gnucobol/gnucobol-3-2.tar.xz
      tar -xvf gnucobol*.tar*
      cd gnucobol*
      ./configure --enable-debug
      make
      sudo make install
      

      Thinking about that... maybe there's a library matchup in your environment?
      What are the outputs of the following commands?

      cobcrun --verbose --version
      ldd ./testbox
      ldd $(which cobcrun)
      
       

      Last edit: Simon Sobisch 2023-12-31
  • Jack Tearle

    Jack Tearle - 2023-12-31

    jack@VPCL237FD:~$ cobcrun --verbose --version
    ldd ./testbox
    ldd $(which cobcrun)
    cobcrun (GnuCOBOL) 3.1.2.0
    Copyright (C) 2020 Free Software Foundation, Inc.
    License GPLv3+: GNU GPL version 3 or later https://gnu.org/licenses/gpl.html
    This is free software; see the source for copying conditions. There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    Written by Roger While, Simon Sobisch, Brian Tiffin
    Built Sep 14 2021 19:23:38
    Packaged Dec 23 2020 12:04:58 UTC

    libcob (GnuCOBOL) 3.1.2.0
    Copyright (C) 2020 Free Software Foundation, Inc.
    License LGPLv3+: GNU LGPL version 3 or later http://gnu.org/licenses/lgpl.html
    This is free software; see the source for copying conditions. There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
    Built Sep 14 2021 19:23:38
    Packaged Dec 23 2020 12:04:58 UTC

    GnuCOBOL 3.1.2 (Sep 14 2021 19:23:38), "11.2.0"
    GMP 6.2.1, libxml2 2.9.12, ncursesw 6.2.20210905, BDB 5.3.28
    linux-vdso.so.1 (0x00007ffccc581000)
    libcob.so.4 => /lib/x86_64-linux-gnu/libcob.so.4 (0x00007ff21b444000)
    libc.so.6 => /lib/x86_64-linux-gnu/libc.so.6 (0x00007ff21b21c000)
    libgmp.so.10 => /lib/x86_64-linux-gnu/libgmp.so.10 (0x00007ff21b19a000)
    libxml2.so.2 => /lib/x86_64-linux-gnu/libxml2.so.2 (0x00007ff21afb8000)
    libncursesw.so.6 => /lib/x86_64-linux-gnu/libncursesw.so.6 (0x00007ff21af7c000)
    libtinfo.so.6 => /lib/x86_64-linux-gnu/libtinfo.so.6 (0x00007ff21af4a000)
    libdb-5.3.so => /lib/x86_64-linux-gnu/libdb-5.3.so (0x00007ff21ad99000)
    /lib64/ld-linux-x86-64.so.2 (0x00007ff21b4cc000)
    libicuuc.so.70 => /lib/x86_64-linux-gnu/libicuuc.so.70 (0x00007ff21ab9e000)
    libz.so.1 => /lib/x86_64-linux-gnu/libz.so.1 (0x00007ff21ab82000)
    liblzma.so.5 => /lib/x86_64-linux-gnu/liblzma.so.5 (0x00007ff21ab57000)
    libm.so.6 => /lib/x86_64-linux-gnu/libm.so.6 (0x00007ff21aa70000)
    libicudata.so.70 => /lib/x86_64-linux-gnu/libicudata.so.70 (0x00007ff218e50000)
    libstdc++.so.6 => /lib/x86_64-linux-gnu/libstdc++.so.6 (0x00007ff218c24000)
    libgcc_s.so.1 => /lib/x86_64-linux-gnu/libgcc_s.so.1 (0x00007ff218c04000)
    linux-vdso.so.1 (0x00007ffc827ec000)
    libcob.so.4 => /lib/x86_64-linux-gnu/libcob.so.4 (0x00007f386ba6f000)
    libc.so.6 => /lib/x86_64-linux-gnu/libc.so.6 (0x00007f386b847000)
    libgmp.so.10 => /lib/x86_64-linux-gnu/libgmp.so.10 (0x00007f386b7c5000)
    libxml2.so.2 => /lib/x86_64-linux-gnu/libxml2.so.2 (0x00007f386b5e3000)
    libncursesw.so.6 => /lib/x86_64-linux-gnu/libncursesw.so.6 (0x00007f386b5a7000)
    libtinfo.so.6 => /lib/x86_64-linux-gnu/libtinfo.so.6 (0x00007f386b575000)
    libdb-5.3.so => /lib/x86_64-linux-gnu/libdb-5.3.so (0x00007f386b3c4000)
    /lib64/ld-linux-x86-64.so.2 (0x00007f386baf7000)
    libicuuc.so.70 => /lib/x86_64-linux-gnu/libicuuc.so.70 (0x00007f386b1c9000)
    libz.so.1 => /lib/x86_64-linux-gnu/libz.so.1 (0x00007f386b1ad000)
    liblzma.so.5 => /lib/x86_64-linux-gnu/liblzma.so.5 (0x00007f386b182000)
    libm.so.6 => /lib/x86_64-linux-gnu/libm.so.6 (0x00007f386b09b000)
    libicudata.so.70 => /lib/x86_64-linux-gnu/libicudata.so.70 (0x00007f386947b000)
    libstdc++.so.6 => /lib/x86_64-linux-gnu/libstdc++.so.6 (0x00007f386924f000)
    libgcc_s.so.1 => /lib/x86_64-linux-gnu/libgcc_s.so.1 (0x00007f386922f000)
    jack@VPCL237FD:~$

    Interestingly, the testsine.cbl and sine.cbl programs that i posted in another thread works correctly.
    see: https://sourceforge.net/p/gnucobol/discussion/help/thread/5ef7013474/?limit=25#24e2
    I thought that this problem might have something to do with screen handling, but moving the screen handling to the subroutine did not make any difference.

     
  • Jack Tearle

    Jack Tearle - 2023-12-31

    What I've did was

    • using the original version (I've mod-edited the split into two sources in)
    • changed box.cbl to have PROGRAM-ID. box. (lower-case)
    • compiled and run with cobc -xj testbox.cbl box.cbl

    I tried this, and while it terminated normally, it did not draw the box. I have made so many changes playing with this, I am going to go back to the original MF code and try again.

     
    👍
    1

    Last edit: Simon Sobisch 2023-12-31
    • Simon Sobisch

      Simon Sobisch - 2023-12-31

      Note that depending on what environment was used to draw the box in the beginning, you may need to update the hex values for the new terminal (an really - you should use hex constants).

       
  • Jack Tearle

    Jack Tearle - 2023-12-31

    It works as separate programs and compiled separately in this environment:
    SCO Openserver 6
    unix:/u/ledg# cobc --version
    cobc (GnuCOBOL) 3.1-rc1.0
    Copyright (C) 2020 Free Software Foundation, Inc.
    License GPLv3+: GNU GPL version 3 or later https://gnu.org/licenses/gpl.html
    This is free software; see the source for copying conditions. There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
    Built Feb 04 2022 19:29:54
    Packaged Jul 01 2020 00:39:38 UTC
    C version "7.3.0"

    I am beginning to think that having had multiple versions on the Linux system has left some library incompatibility.

     
  • Simon Sobisch

    Simon Sobisch - 2024-03-12

    Just out of interest @kitamanswinner: What is the state of your testing?

     
  • Jack Tearle

    Jack Tearle - 2024-03-12

    The sine calculation program that i posted here [https://sourceforge.net/p/gnucobol/discussion/help/thread/5ef7013474/?limit=25#24e2]
    works when compiled using separate complies for the mainline and the function, in both Linux an SCO.
    I thought that the problems with the box program might have to do with the display statements and I moved them around to the subroutine and then calling program, but to no avail.
    I have not done anything since the middle of January; too many year ends to deal with.

     
    👍
    1

Log in to post a comment.