Menu

Debugging with GDB

GnuCOBOL
2022-04-12
2022-05-04
1 2 > >> (Page 1 of 2)
  • Rich Di Iulio

    Rich Di Iulio - 2022-04-12

    Hi All!

    I am debugging with gdb using emacs. It work pretty well, except I do not get line numbers for the source code. So I cannot do break points to speed up my debug session. I ended up using step.

    I tried adding -fdebugging-line to the compile arguments thinking it would do that. I did not. Is there a way get the source code to show the line numbers?

    Oh by the way, I have tried to get the extension CBL-GDB from COBOLworx in VS Codium. Not having much luck for both Linux or Windows.

    Rich Di Iulio

     
  • Simon Sobisch

    Simon Sobisch - 2022-04-12

    cbl-gdb from COBOLworx actually works quite fine, at least in "plain gdb". My experience with its vscodium extension is a bit outdated (and the extension itself wasn't updated), but if you're fine with "plain gdb" I can definitely recommend the "native debug" extension from webfreak (you can still use cbl-gdb's additional commands like "cprint" in the GDB console).
    If you were not aware: to use cbl-gdb you need to compile with its cobcd instead of cobc (the first calls the seconds).

    Back to your original question: -fdebbugging-line activates the lines that start with the debugging directive >>D or fixed-form reference-format D in column 7.

    Just compile with cobc -g (GC 3.x) and you can set breakpoints in gdb at COBOL source like prog.cob:542, in COBOL programs (program-id [case matters] or better program-id with additional underscore). Also possible: prog_:ENTRY_PROG to actually break where the code of PROCEDURE DIVISION starts, also prog_:SECTION_MYMAIN.

     
    • Rich Di Iulio

      Rich Di Iulio - 2022-04-13

      Hey Simon,

      Thank you for your response. What I ended up using cobcd to compile my code. The I run emacs to setup a gdb session. I use the shell variable.

      gdbtool () { emacs --eval "(gdb \"gdb -i=mi -x /usr/bin/cobcd.py $*\")";

      I was able to use the prog.cob:155to set a break point. That answers my question. Thank you.

      Rich Di Iulio

       
      • Simon Sobisch

        Simon Sobisch - 2022-04-13

        Using cobcd also removes any references to the "C" part of the compilations, something you likely want (without it you'd step through both COBOL and C).

        I'm not very familiar with emacs GDB interface, but I guess you have a GDB console where you can show COBOL variables with cprint SOME-VAR now, you also could use that to set COBOL breakpoints (see help cbreak for details).
        You possibly can "adjust" emacs gdb interface allowing you for a tighter integration. I think you'd normally be able to see the C variables in the emacs user interface part, to do the same with COBOL it needs to be adjusted (that's what I did to my local copy of Vim's Termdebug.vim, checking "is the currently shown filetype COBOL, then issue cprint /m $expr instead of -data-evaluate-expression $expr allowing to show COBOL variables on hover). You may want to ask the COBOLworx support for how to use a better emacs integration, at least @jklowden likely can share some hints.

         
  • Rich Di Iulio

    Rich Di Iulio - 2022-04-13

    I tried to contact @jklowden and there is no email address to send to.

     
    • Simon Sobisch

      Simon Sobisch - 2022-04-13

      cbl-gdb comes with a README which had the COBOLworx address in, try this instead (or get his direct mail address from our ChangeLog files).

       
  • Alf

    Alf - 2022-04-18

    Hi,
    cobcd works, but i have a beginner-problem with gdb, too.
    Is it possible to view the whole source at the beginning of gdb ?
    After the start of gdb only the source of the shellcode-copybook get shown.
    After stepping into a30000-processing the content of this paragraph get shown.

    This is, what i mean:
    procedure division.
    copy shellcode-batch.cpy <-- this shellcode performs a30000-processing

    a30000-processing.
    my application :-)
    continue.

    Using "ddd" is the same effect.

     
    • Simon Sobisch

      Simon Sobisch - 2022-04-18

      You may want to check the 'list' command or search for 'tui enable'.

       
    • Rich Di Iulio

      Rich Di Iulio - 2022-04-23

      Hi Alf,

      I use VS Codium and display my source code there. I then refer to it to determine where to set breaks and such. I am also using cobcd to compile my code using a Makefile. Then I use cobcd.py to set debug session.

      Rich Di Iulio

       
      • pottmi

        pottmi - 2022-04-23

        I would love to see someone using VS Codium working with GnuCOBOL.

        Would there be interest in having a monthly show and tell for GnuCOBOL
        where we could meet "face to face" and talk all things GnuCOBOL?

        first meeting could be someone showing us VS Codium.

        on a different meeting I could show off how we use GnuCOBOL to run CICS
        code.

        mod edit to remove some reply-to

         

        Last edit: Brian Tiffin 2022-04-24
        • Mickey White

          Mickey White - 2022-04-23

          Yes, I would like to see VS Codium in use and GDB and GIX and other debuggers and your CICS and any DataBase stuff. Cool.
          Zoom works for me? Do you have a special sharing apt?
          Monthly would be good, too much to do weekly or twice a month....
          I'm in ! Good Idea Rich !

           
          • pottmi

            pottmi - 2022-04-23

            I use zoom all the time but we are an open source group so we may want to
            use https://jitsi.org/

            mod edit to remove some reply-to

             

            Last edit: Brian Tiffin 2022-04-24
            • pottmi

              pottmi - 2022-04-23

              I have an idea...

              How about I sponsor a meetup.com group for GnuCOBOL and gccCOBOL meetups?

              We can get people to sign up there. We would reach more people who might
              otherwise not stumble on the mailing list.

              How about the stakeholders in GnuCOBOL and gccCOBOL sound off and I will
              create it and sponsor it if it is a consensus to do it.

              mod edit to remove some reply-to

               
              👍
              1

              Last edit: Brian Tiffin 2022-04-24
              • Brian Tiffin

                Brian Tiffin - 2022-04-24

                Gee, not sure if that thumbs up sounded loud enough. ;-) I'd be in, Michael.

                But, I might go all subliminal and try and lead people to the world of Vim instead. ;-)

                That, and I gotta get back on a more capable machine that works with the new GixIDE by Marco Ridoni, and run it through some paces.

                Have good,
                Blue

                 

                Last edit: Brian Tiffin 2022-04-24
              • Simon Sobisch

                Simon Sobisch - 2022-04-24

                I'm personally not in favor of registering anywhere else. We already all "meet" here.

                One thing that could be sponsored is a Jitsi room for GnuCOBOL where we can meet "more directly" and also do screen sharing / presentation.

                If I remember correctly (the only press statement I've found quick was https://www.fsf.org/news/free-software-foundation-announces-freedom-respecting-videoconferencing-for-its-associate-members) it would be possible for a FSF associate member (which is not that expensive) to create rooms and invite people to the room sharing the link. Sponsoring the copyright owners of GnuCOBOL doesn't sound too bad in any case, so @pottmi what do you think about that?

                 
                • pottmi

                  pottmi - 2022-04-24

                  "We already all "meet" here." agreed, Meetup will not change that.

                  Meetup is not really a forum for chatting (other than to arrange the
                  meeting) so people will still use the mailing list.

                  It is really a platform for new people to find groups that they are
                  interested in and also a way to have people RSVP to the event.

                  Other Open Source groups I am involved with are using meetup with success:

                  Atlanta Linux Enthusiasts:
                  https://www.meetup.com/ALE-Atlanta-Linux-Enthusiasts/events/285355610/

                  UniForum Chicago: https://www.meetup.com/UniForum-Chicago/

                  Atlanta Java User Group: https://www.meetup.com/atlantajug/

                  BTW: The Link you sent for the FSF conferencing system is Jitsi. I have
                  used it on my Mac and it worked great.

                  You are a stakeholder so if you say you don't want it I won't register it
                  unless other stakeholders say they want it.

                  You could also agree to register it for a year and if it does not work well
                  i will shut it down.

                  mod edit to remove some reply-to

                   

                  Last edit: Brian Tiffin 2022-04-24
            • Brian Tiffin

              Brian Tiffin - 2022-04-24

              There is also GNU Jami; worked pretty well between Canada and Germany when Simon and I were trying it out. https://jami.net/

              Cheers,
              Blue

               
  • Rich Di Iulio

    Rich Di Iulio - 2022-04-23

    Hi All!

    Well, I have been able to get Emacs to work in both Linux and Windows. I am using Emacs and have a init.el file. I have the following placed in the init file.

     (setq gdb-many-windows t)                 <-- display multiple
                                                                                                                                        windows for gdb
    
    (global-set-key [f7]    'cobol-debugger)  <-- function assigned to
                                                                                                                                        F7 (Windows)
    
     (defun cobol-debugger ()
       (interactive)
       (let* ((guess (concat "gdb -i=mi -x " debug-script " "))
              (arg (read-from-minibuffer "Run gdb : "
                                         guess nil nil 'gdb-my-history)))
         (gdb arg)))
    

    Attached is screenshots showing the process. If there are any questions, please let me know.

    Rich Di Iulio

     
    • Simon Sobisch

      Simon Sobisch - 2022-04-24

      Emacs seems to believe it is debugging cobcd.py. Maybe it gets better if you place that -x before the -i? The main "issue" open here is that the locals window shows the locals that GDB sees, you'd like it to show the locals that cobcd.py sees. I think to do this you'd need to tweak the communication with GDB (not using the common mi commands for this but use cprint /m * instead). I guess there's an option to add a new "cobcd.py locals" window so you could actually query both easily, but I'm not an Emacs person so far.

      If you did not do that already: try cp ? in the gdb console window (to show the variables "near" the current line) and cp some-var-name="value" to assign COBOL variables.

       
      • Rich Di Iulio

        Rich Di Iulio - 2022-04-26

        Hey Simon,

        The gdb does not work without -i=mi. The way I have the command setup is the way it needs to be. I do like the fact I can use abbreviations for the commands. Thank you Simon.

         
        • Rich Di Iulio

          Rich Di Iulio - 2022-04-30

          Well, I thought I was able to debug under Windows, but cannot examine my variables. It does step through the code.

          The error I am getting is the following:

          Traceback (most recent call last):
            File "c:/gc/gc312-bdb-m32/bin/cobcd.py", line 4315, in ReadAndParseVariableString
              variable_string = variable_string_memview.tobytes().decode('ascii')  # plain string generate by cobcd
          UnicodeDecodeError: 'ascii' codec can't decode byte 0xb0 in position 14635: ordinal not in range(128)
          Traceback (most recent call last):
            File "c:/gc/gc312-bdb-m32/bin/cobcd.py", line 4315, in ReadAndParseVariableString
              variable_string = variable_string_memview.tobytes().decode('ascii')  # plain string generate by cobcd
          UnicodeDecodeError: 'ascii' codec can't decode byte 0xb0 in position 14635: ordinal not in range(128)
          This doesn't look like a COBOL frame.
          

          Not sure what is going on. It works with Linux, but I want to debug on Windows to make sure I have the environment setup correctly.

          Rich Di Iulio

           
          • Simon Sobisch

            Simon Sobisch - 2022-04-30

            Very likely you have a different version of python in both environments - you can check in gdb using

            py print (sys.version)
            

            Side note: I've worked quite a bit on this and similar issues with a forked version of cobcd.py. If someone is willing to take the changes apart and provide patches upstream I could post it on Monday for this purpose.

             
            • Rich Di Iulio

              Rich Di Iulio - 2022-04-30

              The version is as follow:

                  `3.9.10 (main, Mar 14 2022, 18:53:08 (GCC 11.2.0 32 bit))`
              
               
              • Simon Sobisch

                Simon Sobisch - 2022-04-30

                ... and the working (or not working) other version?

                Hm, looking at the message again it seems that there's a "strange" character in there when reading the cobcd generated debug symbol information - there should be only ascii data in.

                Can you produce a minimal reproducer and post it along with the error message and the generated C files from cobcd -save-temps (both from the working and from the not working machine)? This would allow me to have a look; maybe there is an issue in the code generation.

                 
                • Rich Di Iulio

                  Rich Di Iulio - 2022-05-03

                  Hi Simon,

                  I have not been able to provide you with information you need to help. The basic thing is that it works on Linux (sort of) and does not work on Windows.

                  Now I have a laptop and a VM running Linux Mint 20.3. The version of the following software:

                                       GnuCOBOL 3.1.2.0
                                       CBL-GDB  4.27.1
                                       gcc      9.4.0
                                       gdb      9.2
                                       python   3.8.10
                  

                  While in a gdb session the following CBL-GDB commands:

                                        cstart    yes
                                        cbreak    no
                                        cnext     yes
                                        cprint    yes
                                        step      yes
                                        break     yes
                  

                  Under Windows, I got so confused, I deleted all the builds and started over. I have attached the cobc -info from my laptop. More information to come...

                  Rich Di Iulio

                   
1 2 > >> (Page 1 of 2)

Log in to post a comment.