gnucobol-users
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

Fwd: Re: [open-cobol-list] OPEN OUTPUT Segemtation Fault


From: John R. Culleton
Subject: Fwd: Re: [open-cobol-list] OPEN OUTPUT Segemtation Fault
Date: Thu Dec 1 05:45:02 2005
User-agent: KMail/1.7.2

Benjamin Kimpel is having trouble reaching the list directly
except in html format. Here is his inquiry as he stated it to me:


----------  Forwarded Message  ----------

Subject: Re: [open-cobol-list] OPEN OUTPUT Segemtation Fault
Date: Thursday 01 December 2005 05:26 am
From: Benjamin Klimpel <address@hidden>
To: address@hidden

Hello John Culleton

sorry for the html code, but im forced to send emals in html code, cause
the my normal email accout issn't compatible with the cobol maillist.

Heres the Email again without html code:

Hello, i have some questions about opencobol. I have suscessful compiled this
 source, but the "OPEN OUTPUT FD-ADRBST" Command don't to what it should do,
 the File "ADRBST" should creat, but when i started to compiled programm
 there comes a Segmentaion Fault. I input some debug printfs in fileio.c in
 the function cob_open, when the programm try to open the file, there error
 comes.

May you can help me

best regards

Benjamin

//////////////////////////////////////////////////////////////////////////
*inspect
*symbols
*SEARCH $SYSTEM.ZTCPIP.LIBINETL
*SEARCH $SYSTEM.SYSTEM.CLARGE
*SEARCH $SYSTEM.SYSTEM.CLULIB
*ENV COMMON
*save all
*********************************
*                               *
*  REORGANISATION FUER BULDHIS  *
*  ===========================  *
*                               *
*****************************
 ****
 IDENTIFICATION DIVISION.
 PROGRAM-ID. UPTESTO.
 AUTHOR.     SIMON.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SOURCE-COMPUTER. T16.
 OBJECT-COMPUTER. T16.
 SPECIAL-NAMES.
    DECIMAL-POINT IS COMMA.

 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
*
*    Druck-File
*
     SELECT FD-ADRBST ASSIGN TO "ADRBST"
            organization indexed
            access mode is random
            file status is STAT-DATEI
            record key ADR-PK OF ADRBST
            alternate record key ADR-AK-KURZNAME WITH DUPLICATES.

 DATA DIVISION.
 FILE SECTION.
*
*    Umsatz-Drucker
*
 FD  FD-ADRBST
     LABEL RECORD IS STANDARD.
  01 ADRBST.
    02 ADR.
      03 ADR-PK.
        04 ADR-PK-ADR-NR.
          05 ADR-PK-KTO.
            06 ADR-PK-BST.
              07 ADR-PK-AZ.
                08 ADR-PK-MAN.
                  09 ADR-PK-JAHR.
                    10 ADR-JAHR
  PIC S9(4)      COMP.
                  09 ADR-MAN         PIC S9(4)      COMP.
                08 ADR-AZ            PIC S9(4)      COMP.
              07 ADR-BST             PIC S9(4)      COMP.
            06 ADR-KTO-NR            PIC S9(9)      COMP.
          05 ADR-ADR-NR              PIC S9(4)      COMP.
      03 ADR-AK-KURZNAME.
        04 ADR-AK-MAN.
          05 ADR-MAN-ADR             PIC S9(4)      COMP.
          05 ADR-KURZ-FAMNAME        PIC X(5).
          05 ADR-KURZ-VORNAME        PIC X(3).
          05 ADR-KURZ-ORT            PIC X(4).
      03 ADR-ANSCHRIFT.
        04 ADR-MZF                   PIC X(30).
        04 ADR-KZ-MAENNL-WEIBL       PIC S9(4)      COMP.
        04 ADR-NAME1                 PIC X(50).
        04 ADR-NAME2                 PIC X(50).
        04 ADR-ZUSATZ                PIC X(45).
        04 ADR-STRASSE               PIC X(45).
        04 ADR-LAENDER-KZ            PIC X(4).

         04 ADR-PLZ                   PIC X(6).
        04 ADR-ORT                   PIC X(25).
        04 FILLER                    PIC X(1).
        04 ADR-EROF-DAT              PIC S9(9)      COMP.
        04 ADR-GEBDAT                PIC S9(9)      COMP.
        04 ADR-TELNR-GESCH           PIC X(14).
        04 ADR-TELNR-PRIVAT          PIC X(14).
        04 ADR-TELNR-BANK            PIC X(14).
        04 ADR-DATUM-LAE-AEND        PIC S9(9)      COMP.
        04 ADR-KZ-INFO               PIC 9.
        04 FILLER                    PIC X.
        04 ADR-UPDATE-ZAEHL          PIC S9(4)      COMP.

/
 WORKING-STORAGE SECTION.
 01 STAT-DATEI                         PIC XX.
 01 RESULT                             PIC S9(4)     COMP.

/
 PROCEDURE DIVISION.
 ERSTE SECTION.

  OPEN OUTPUT FD-ADRBST.
  INITIALIZE ADRBST
  MOVE 4711 TO ADR-KTO-NR
  WRITE ADRBST
  CLOSE FD-ADRBST
         .

 ERS
 T-EXIT.
         STOP RUN.

         EXIT.

//////////////////////////////////////////////////////////////////////////


best regards

Benjamin Klimpel

-------------------------------------------------------



reply via email to

[Prev in Thread] Current Thread [Next in Thread]