public inbox for sourcenav@sourceware.org
 help / color / mirror / Atom feed
* COBOL parser
@ 2000-12-29 14:36 alex.shneer
  2000-12-31 17:25 ` Ben Elliston
  0 siblings, 1 reply; 3+ messages in thread
From: alex.shneer @ 2000-12-29 14:36 UTC (permalink / raw)
  To: sourcenav

Hi,
can somebody tell why COBOL parser is including surrounding quotes in the
function names?

"Symbol Browser" shows the following error when I'm selecting
"calling_procedure" or "called_procedure"
from the list of functions by clicking on the function icon.

==========================================================

list element in quotes followed by "(fu)" instead of space
    while executing
"lindex [$tree get $idx] 0"
    (proc "Retriever&@@expand_classes" body line 35)
    invoked from within
"expand_classes .multisymbr-1.symbr 10 24 display_contents"
    invoked from within
"Retriever& @@ expand_classes .multisymbr-1.symbr 10 24 display_contents"
    invoked from within
"Retriever& @@ expand_classes $this $x $y display_contents"
    (object ".multisymbr-1.symbr" method "Retr&@@handle_click" body line 2)
    invoked from within
".multisymbr-1.symbr handle_click 10 24"
    (command bound to event)

========================================================

Cross reference tool also shows error and refuses to recognize that
"called_procedure"
is refered by "calling_procedure"

There are examples of the procedures, each should be in a separate file:
========================================================
calling_procedure.cbl:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. "calling_procedure".
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       LINKAGE SECTION.
       PROCEDURE DIVISION.
       A-MAIN SECTION.
       A-00.
        CALL  "called_procedure".
       A-EXIT.
           EXIT.


========================================================
called_procedure.cbl

       IDENTIFICATION DIVISION.
       PROGRAM-ID. "called_procedure".
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       LINKAGE SECTION.
       PROCEDURE DIVISION.
       A-MAIN SECTION.
       A-00.
           PERFORM  B-INIT.
           PERFORM  Z-FINISH.
       A-EXIT.
           EXIT.

       B-INIT SECTION.
       B-00.
       B-EXIT.
           EXIT.
       Z-FINISH SECTION.
       Z-00.
       Z-EXIT.
           EXIT PROGRAM.

==========================================================


^ permalink raw reply	[flat|nested] 3+ messages in thread

* Re: COBOL parser
  2000-12-29 14:36 COBOL parser alex.shneer
@ 2000-12-31 17:25 ` Ben Elliston
  0 siblings, 0 replies; 3+ messages in thread
From: Ben Elliston @ 2000-12-31 17:25 UTC (permalink / raw)
  To: alex.shneer; +Cc: sourcenav

Hi Alex,

   can somebody tell why COBOL parser is including surrounding quotes in
   the function names?

Because your program identifiers have quotes in the source:

          PROGRAM-ID. "calling_procedure".

Why have you put quotes around the program-id?  I'm not very familiar with
COBOL at all, but every COBOL program I've ever seen have not included
quotes.

Ben

^ permalink raw reply	[flat|nested] 3+ messages in thread

* COBOL parser
@ 2001-01-05  9:06 alex.shneer
  0 siblings, 0 replies; 3+ messages in thread
From: alex.shneer @ 2001-01-05  9:06 UTC (permalink / raw)
  To: sourcenav

Hi,Ben.

I fixed a bug in the source navigator obrowser's Parser.c.

Regards,
Alex Shneer
alex.shneer@verizon.com

--------------------------------------------------
Text description
--------------------------------------------------
snavigator/parsers/cobol/Parser.c: changed parameters passed to MakeIdent
                                                                       to
remove quotes from a string
                                                                       when
 it is used as an indentifier
--------------------------------------------------
ChangeLog entry
--------------------------------------------------
2001-01-01  Alex Shneer  <alex.shneer@verizon.com>

snavigator/parsers/cobol/Parser.c: changed parameters passed to MakeIdent
                                                                       to
remove quotes from a string
                                                                       when
 it is used as an indentifier

--------------------------------------------------
diff -c3p SN452-source/snavigator/parsers/cobol/Parser.c Parser.c
--------------------------------------------------

*** SN452-source/snavigator/parsers/cobol/Parser.c      Fri Feb 11 18:52:03
 2000
--- Parser.c   Fri Jan  5 11:50:27 2001
*************** case 2949: yyDecrement (5) yySetNT (yyNT
*** 12631,12637 ****
   ;
  {  char word [128];
               StGetString (yyA [3].Scan.string.Value, word);
!              yyA [3].Scan.name.Ident = MakeIdent (word, strlen (word));
               (void) DeclareLabel (yyA [3].Scan, lPROGRAM, PrevEPos); ; }
;

  } break;
--- 12631,12637 ----
   ;
  {  char word [128];
               StGetString (yyA [3].Scan.string.Value, word);
!              yyA [3].Scan.name.Ident = MakeIdent (&word[1], strlen
(word)-2);
               (void) DeclareLabel (yyA [3].Scan, lPROGRAM, PrevEPos); ; }
;

  } break;
*************** case 3860: yyDecrement (1) yySetNT (yyNT
*** 14707,14713 ****
   ;
  {  char word [128];
               StGetString (yyA [0].Scan.string.Value, word);
!              yyA [0].Scan.name.Ident = MakeIdent (word, strlen (word));
               UseLabelExtern (yyA [0].Scan); ; } ;

  } break;
--- 14707,14713 ----
   ;
  {  char word [128];
               StGetString (yyA [0].Scan.string.Value, word);
!              yyA [0].Scan.name.Ident = MakeIdent (&word[1], strlen
(word)-2);
               UseLabelExtern (yyA [0].Scan); ; } ;

  } break;
*************** case 3862: yyDecrement (2) yySetNT (yyNT
*** 14723,14729 ****
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (word, strlen (word));
               UseLabelExtern (yyA [1].Scan);
               UseLabelExtern (yyA [0].Scan); ; } ;

--- 14723,14729 ----
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (&word[1], strlen
(word)-2);
               UseLabelExtern (yyA [1].Scan);
               UseLabelExtern (yyA [0].Scan); ; } ;

*************** case 4001: yyDecrement (2) yySetNT (yyNT
*** 15032,15038 ****
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (word, strlen (word));
               (void) DeclareLabel (yyA [1].Scan, lENTRY, PrevEPos); ; } ;

  } break;
--- 15032,15038 ----
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (&word[1], strlen
(word)-2);
               (void) DeclareLabel (yyA [1].Scan, lENTRY, PrevEPos); ; } ;

  } break;
*************** case 4002: yyDecrement (4) yySetNT (yyNT
*** 15041,15047 ****
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (word, strlen (word));
               (void) DeclareLabel (yyA [1].Scan, lENTRY, PrevEPos); ; } ;

  } break;
--- 15041,15047 ----
   ;
  {  char word [128];
               StGetString (yyA [1].Scan.string.Value, word);
!              yyA [1].Scan.name.Ident = MakeIdent (&word[1], strlen
(word)-2);
               (void) DeclareLabel (yyA [1].Scan, lENTRY, PrevEPos); ; } ;

  } break;


^ permalink raw reply	[flat|nested] 3+ messages in thread

end of thread, other threads:[~2001-01-05  9:06 UTC | newest]

Thread overview: 3+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2000-12-29 14:36 COBOL parser alex.shneer
2000-12-31 17:25 ` Ben Elliston
2001-01-05  9:06 alex.shneer

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).