[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference orarep::nomahs::dectrace_v20

Title:DECtrace V2.0 and All-in-1 Perf Rpts conf.
Notice:Kits+Doc, 2 | Patches, 3
Moderator:OMYGOD::LAVASH
Created:Mon Apr 26 1993
Last Modified:Mon Jun 02 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:467
Total number of notes:2058

464.0. "EPC-E-FMT_DCF_ASCLONG error " by BROKE::BASTINE () Tue May 06 1997 13:32

Customer is receiving the following errors:

$ collect format online online
%EPC-I-FMT_RDB_CREATE, Creating database ONLINE
%EPC-S-FMT_RDB_SUCCESS, Successfully created database
%EPC-I-FMT_DCF_BEGIN, Formatting data file ONLINE
%EPC-E-FMT_DCF_FAILURE, Failed formatting at block 6 of file ONLINE
%EPC-E-FMT_DCF_ASCLONG, ASCII string in event 1 of facility 2048 is
longer than maximum size allowed
%EPC-E-FMT_FAILURE, Formatting failed
%EPC-E-OPFAIL, Operation failed

I understand that this error is a result of some data being stored in a 
field by the facility that is greater than the field length.
I am not sure how to pinpoint what that field is, or how this customers
code can check for that problem... any suggestions?

Below is the customers code that uses some Dectrace calls.  If you need the
.DAT file it created, please let me know and I'll get a copy of it.

Thanks,
Renee

The Oracle Trace version number is as follows.
$ collect sho vers
Oracle Trace Version V2.2

The following is the listing of the test program that creates the data
captured by Oracle trace.
TESTER                                                          
2-May-1997 16:25:31    VAX COBOL V5.3-40                   Page   1
Source Listing                                                 
18-Apr-1997 15:31:09    DISK$DEV1:[TECH_SUPPORT.AGEORGE]TEST.COB;23

    1         IDENTIFICATION DIVISION.
    2         PROGRAM-ID. tester.
    3
    4         ENVIRONMENT DIVISION.
    5         CONFIGURATION SECTION.
    6         SOURCE-COMPUTER.
    7             VAX WITH DEBUGGING MODE.
    8         OBJECT-COMPUTER.
    9             VAX.
   10
   11         DATA DIVISION.
   12         WORKING-STORAGE SECTION.
   13         COPY "instrument_facility".
   14L       *+
   15L       * PROGRAM : [tbs]
   16L       *
   17L       * PROGRAM DESCRIPTION:
   18L       *
   19L       *       {tbs}
   20L       *
   21L       * AUTHORS:
   22L       *
   23L       *       {tbs}
   24L       *
   25L       * CREATION DATE: {tbs}
   26L       *
   27L       *
   28L       * DESIGN ISSUES:
   29L       *
   30L       *       [tbs]
   31L       *
   32L       * MODIFICATION HISTORY:
   33L       *
   34L       *       [chg-date-author-desc]
   35L       *
   36L       *-
   37L        01 instrument_facility.
   38L            05 online               pic 9(9) comp value 2048.
   39L            05 pc_express   pic 9(9) comp value 2049.
   40L            05 mmt          pic 9(9) comp value 2050.
   41L            05 tpp          pic 9(9) comp value 2051.
   42L            05 account_manager      pic 9(9) comp value 2052.
   43L
   44L        01 instrument_registration.
   45L            05 online pic x(11) value "CIBC Online".                   
   46L            05 pc_express pic x(10) value "PC Express".
   47L            05 mmt pic x(19) value "Money Market Trader".
   48L            05 tpp pic x(19) value "Third Party Payment".
   49L            05 account_manager pic x(15) value "Account Manager".
   50L
   51L        01 instrument_version.
   52L            05 online pic x(3) value "001".
   53L            05 pc_express pic x(3) value "001".
   54L            05 mmt pic x(3) value "001".
   55L            05 tpp pic x(3) value "001".
   56L            05 account_manager pic x(3) value "001".
   57         COPY "instrument_online".

TESTER                                                          
2-May-1997 16:25:31    VAX COBOL V5.3-40                   Page   2
Source Listing                                                 
18-Apr-1997 15:41:29    INSTRUMENT_ONLINE.LIB;5 (1)

   58L        77 max-events                       pic 9(9) comp value
128.
   59L        77 event-file-download              pic 9(9) comp value 1.
   60L        77 event-session-duration   pic 9(9) comp value 2.
   61L        77 event-file-create-rpd    pic 9(9) comp value 3.
   62L        77 event-file-create-exp    pic 9(9) comp value 4.
   63L        77 event-do-online-service  pic 9(9) comp value 5.
   64L
   65L        77 event-item-username              pic 9(9) comp value 1.
   66L        77 event-item-network               pic 9(9) comp value 1.
   67L        77 event-item-bytes-transfer        pic 9(9) comp value 1.
   68L
   69L        01 event-flags-file-download.
   70L            05 event-flags          pic 9(9) comp occurs 128
times.
   71L        01 event-item-flags-file-download.
   72L            05 event-item-flags     pic 9(9) comp occurs 128
times.
   73L
   74L       *01 event-data-file-download.
   75L       *    05 username_length              pic x value x"06".
   76L       *    05 username             pic x(6).
   77L       *    05 network_length               pic x value x"40".
   78L       *    05 network                      pic x(64).
   79L       *    05 bytes_b4_tsf                 pic 9(9) comp.
   80L       *    05 bytes_after_tsf              pic 9(9) comp.
   81L        01 event-data-file-download-start.
   82L            05 username_length              pic x value x"06".
   83L            05 username             pic x(6).                                                               
   84L            05 network_length               pic x value x"20".
   85L            05 network                      pic x(32).
   86L        01 event-data-file-download-end.
   87L            05 bytes_b4_tsf                 pic 9(9) comp.
   88L            05 bytes_after_tsf              pic 9(9) comp.
   89L
   90L        01 handle-file-download     pic 9(9) comp.
   91L        01 handle-session-duration  pic 9(9) comp.
   92L        01 handle-file-create-rpd   pic 9(9) comp.
   93L        01 handle-file-create-exp   pic 9(9) comp.
   94L        01 handle-do-online-service         pic 9(9) comp.
   95         01 status-code pic 9(9) comp.
   96         01 input-file-status pic xx.
   97         01 ksn pic x(8) value x"0500000000000046".
   98         01 rand.
   99             03 one pic 9(9) comp value 0.
  100             03 two pic 9(9) comp value 0.
  101         01 five-one-two pic 9(9) comp value 512.
  102         01 encrypt pic 9(9) comp value 1.
  103         01 compress pic 9(9) comp value 0.
  104         01 bytes_in pic 9(9) comp.
  105         01 bytes_out pic 9(9) comp.
  106         01 error-code pic 9(9) comp.
  107         01 ivin.
  108             03 filler pic 9(9) comp value 0.
  109             03 filler pic 9(9) comp value 0.
  110         01 ivout.
  111             03 filler pic 9(9) comp value 0.
  112             03 filler pic 9(9) comp value 0.
  113         PROCEDURE DIVISION.
  114


TESTER                                                          
2-May-1997 16:25:31    VAX COBOL V5.3-40                   Page   3
Source Listing                                                 
18-Apr-1997 15:31:09    DISK$DEV1:[TECH_SUPPORT.AGEORGE]TEST.COB;23

  115         main.
  116             CALL "instrument_initialize"
  117                     USING BY VALUE online of instrument_facility
  118             BY DESCRIPTOR online of instrument_registration
  119             BY DESCRIPTOR online of instrument_version
  120             BY REFERENCE event-flags-file-download
  121                     GIVING status-code
  122             END-CALL.
  123             move "test" to username
  124             move "network" to network
  125             PERFORM 10 TIMES
  126             call "instrument_start_event"
  127                 using BY VALUE online of instrument_facility,
event-file-download                                         
  128                 by reference handle-file-download
  129                 by descriptor event-data-file-download-start
  130                 GIVING status-code
  131             END-CALL
  132             CALL "expbaienccmp"
  133                 USING BY DESCRIPTOR "[.test]*.%"
"[.test]foolish.output" BY REFERENCE ksn rand BY VALUE encrypt compress
  134                 BY REFERENCE bytes_b4_tsf bytes_after_tsf
  135                 GIVING error-code
  136             END-CALL
  137             call "instrument_end_event"
  138                 using BY VALUE online of instrument_facility,
event-file-download
  139                 by reference handle-file-download
  140                 by descriptor event-data-file-download-end
  141                 GIVING status-code
  142             END-CALL
  143             END-PERFORM
  144
  145             stop run.
  146         END PROGRAM tester.

TESTER                                                          
2-May-1997 16:25:31    VAX COBOL V5.3-40                   Page   4
Compilation Summary                                            
18-Apr-1997 15:31:09    DISK$DEV1:[TECH_SUPPORT.AGEORGE]TEST.COB;23

PROGRAM SECTIONS

    Name                                Bytes   Attributes

  0 $CODE                                 216     PIC   CON   REL  
LCL   SHR   EXE   RD NOWRT Align(2)
  1 $LOCAL                                808     PIC   CON   REL   LCL
NOSHR NOEXE   RD   WRT Align(2)
  2 $PDATA                                264     PIC   CON   REL  
LCL   SHR NOEXE   RD NOWRT Align(2)
  3 COB$NAMES_____2                        24     PIC   CON   REL  
LCL   SHR NOEXE   RD NOWRT Align(2)
  4 COB$NAMES_____4                         7     PIC   CON   REL  
LCL   SHR NOEXE   RD NOWRT Align(2)


DIAGNOSTICS

    Informational:      40 (suppressed by command qualifier)


COMMAND QUALIFIERS

    COBOL /DEBUG/LIST/COPY TEST

    /COPY_LIST  /NOMACHINE_CODE  /NOCROSS_REFERENCE
    /NOANSI_FORMAT  /NOSEQUENCE_CHECK  /NOMAP
    /NOTRUNCATE  /NOAUDIT  /NOCONDITIONALS
    /CHECK=(NOPERFORM,NOBOUNDS,NODUPLICATE_KEYS) 
/DEBUG=(SYMBOLS,TRACEBACK)
    /WARNINGS=(NOSTANDARD,OTHER,NOINFORMATION)  /NODEPENDENCY_DATA
    /STANDARD=(NOSYNTAX,NOPDP11,NOV3,85,NOALPHA_AXP)  /NOFIPS
    /LIST  /OBJECT /NODIAGNOSTICS /NOFLAGGER /NOANALYSIS_DATA
    /INSTRUCTION_SET=DECIMAL_STRING /DESIGN=(NOPLACEHOLDERS,NOCOMMENTS)               
    /NATIONALITY=US


STATISTICS

    Run Time:           0.11 seconds
    Elapsed Time:       0.70 seconds
    Page Faults:        593
    Dynamic Memory:     427 pages

The following is the facility definition that corresponds to the data
collected by the above program.
$collect
CREATE DEFINITION online 2048 /REPLACE /VERSION="001" /OPTIONS

item username ascic/char=printable/id=1/report_header="Username"-
/report_width=6/usage_type=text/size=6

item network ascic/char=printable/id=2/report_header="Port Name"-
/report_width=32/usage_type=text/size=32

item bytes_b4_tsf longword/char=printable/id=3/report_header="Bytes
before"-
/report_width=8/usage_type=level

item bytes_after_tsf longword/char=printable/id=4/report_header="Bytes
after."-
/report_width=8/usage_type=level

event file_download/identifier=1-
/items=(username,network,bytes_b4_tsf,bytes_after_tsf,resource_items)-
/start=(username,network,resource_items)-
/end=(bytes_b4_tsf,bytes_after_tsf,resource_items)-
/report_header="File Download"

!event session_duraton/identifier=2-
!/items=(username,network,bytes_b4_tsf,bytes_after_tsf,resource_items)-
!/report_header="Duration"


!event make_rpd_file/identifier=3-
!/items=(username,network,bytes_b4_tsf,bytes_after_tsf,resource_items)-
!/report_header="Make Rapidtrns"

!event make_exp_file/identifier=4-
!/items=(username,network,bytes_b4_tsf,bytes_after_tsf,resource_items)-
!/report_header="Make Express"

!event Online_service/identifier=5-
!/items=(username,network,bytes_b4_tsf,bytes_after_tsf,resource_items)-
!/report_header="Online Services"

T.RTitleUserPersonal
Name
DateLines
464.1is a byte a byte??OOTOOL::LAVASHSame as it ever was...Fri May 09 1997 16:3412
That error says that one of the strings in event 1 is too long.
ASCIC data type means one byte length, then string.

Does COBOL allow for 1 byte variables?  Is the record definition
of the event buffer padding a WORD here instead of a BYTE?

To test this theory you could change the type to ASCIW...

Otherwise you have a length greater than 6 or 32 passed in one of
these fields.

George
464.2Asciw didn't helpBROKE::BASTINEWed May 14 1997 13:3913
According to the customer the ASCIC data type is a byte.  To test the theory
they did change the datatypes to ASCIW and ran into the same problem.

He is going to send me a dump of the program and what you see for datatypes
using the asciw.  

Is there anything else you might need to help him find what field is the 
offending one?

Thanks,
Renee

I'll post the dump when I get it.
464.32 ways to goOOTOOL::LAVASHSame as it ever was...Thu May 15 1997 14:3421
>According to the customer the ASCIC data type is a byte.  To test the theory
>they did change the datatypes to ASCIW and ran into the same problem.

>He is going to send me a dump of the program and what you see for datatypes
>using the asciw.  

>Is there anything else you might need to help him find what field is the 
>offending one?

have them send the .dat file.

We can format here and find it.

Or they could do the trial and error thing...

Modify their facility definition, increase the max lenght of one item,
rerun, see if it formats, then try the other.

Have the used the debugger and verfied the lengths being passed in???

George