ibmi-brunch-learn

Announcement

Collapse
No announcement yet.

ICF file handling in COBOL

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • ICF file handling in COBOL

    Hi,
    I have written a small COBOL program which involves ICF file handling and compiled it successfully. But, during run of this program, the WRITE operation to the ICF file COMICFON2 is ended with error[i.e File status = "9N"]. Even, the recovery operation was also unsuccessful[i.e File Status = "9C"]. I could not find the reason for the same. Kindly help in this regard.

    Note: My user-Id has "*ALL" authority to this ICF file object. The source code and output of my program is given below.
    The following are the few attribute values of the above ICF file:
    ACQPGMDEV = *NONE
    MAXPGMDEV = 6 [i.e Multiple Device]

    Code:
    [B][U]Sample Code:[/U][/B]
    
           IDENTIFICATION DIVISION.                                         
           PROGRAM-ID.    HANDYICF.                                          
           ENVIRONMENT DIVISION.                                            
           CONFIGURATION SECTION.                                           
           SOURCE-COMPUTER. AS-400.                                         
           OBJECT-COMPUTER. AS-400.                                         
          *                                                                 
           INPUT-OUTPUT SECTION.                                            
           FILE-CONTROL.                                                    
                SELECT A-LINEA    ASSIGN       TO WORKSTATION-COMICFON2-SI  
                              ORGANIZATION    TRANSACTION                   
                              FILE STATUS     FS-LINEA                      
          *                                   RT-LINEA                      
                              CONTROL-AREA    AC-LINEA.                     
           DATA DIVISION.                                                   
           FILE SECTION.                                                    
           FD  A-LINEA                                                      
               LABEL RECORDS IS STANDARD.                                   
           01  R-LINEA.                                                     
               COPY DDS-REGDATA     OF COMICFON2.                           
          *01  R-LINEA-NULO.                                                
          *    COPY DDS-REGNULO     OF COMICFON2.                           
                                                                            
           WORKING-STORAGE SECTION.                                         
           77  FS-LINEA    PIC X(02) VALUE ZEROS.                           
           77  W-FORMATO   PIC X(10).                                       
           01     IND-ON        PIC  1            VALUE B"1".               
           01     IND-OFF       PIC  1            VALUE B"0".               
           77  XX-MENSAJE  PIC X(512).                                      
                                                                            
           01      AC-LINEA.                                                
             05    AC-COMANDO      PIC  X(02).                              
             05    AC-PGMDEV       PIC  X(10).                              
             05    AC-NOMFMT       PIC  X(10).                              
                                                                            
           01     IND-AREA.                                                 
             05   IND-TRNRND    PIC  1         INDIC 01.                    
             05   IND-RCVENDGRP PIC  1         INDIC 02.                    
             05   IND-RCVFAIL   PIC  1         INDIC 03.                    
             05   IND-ENDGRP    PIC  1         INDIC 12.                    
          *           ENDGRP TERMINA TODAS LAS SESIONES                     
             05   IND-FAIL      PIC  1         INDIC 13.                    
             05   IND-RQSWRT    PIC  1         INDIC 14.                    
             05   IND-ALWWRT    PIC  1         INDIC 15.                    
             05   IND-INVITE    PIC  1         INDIC 16.                    
             05   IND-FRCDTA    PIC  1         INDIC 17.                    
             05   IND-CANCEL    PIC  1         INDIC 18.                    
             05   IND-EOS       PIC  1         INDIC 19.                    
             05   IND-EVOKE     PIC  1         INDIC 30.                    
             05   IND-DETACH    PIC  1         INDIC 32.                    
             05   IND-RCVDETACH PIC  1         INDIC 42.                    
             05   IND-CONFIRM   PIC  1         INDIC 40.                    
             05   IND-RCVCFM    PIC  1         INDIC 45.                    
    
           PROCEDURE DIVISION.                                              
                 OPEN I-O A-LINEA.                                          
                 DISPLAY "FILE STATUS:" FS-LINEA.                           
                                                                            
                 MOVE    IND-OFF       TO IND-TRNRND                        
                 MOVE    IND-ON        TO IND-INVITE                        
                 MOVE    "PANDIAN K"   TO REGDATA-O                         
                 MOVE    "REGDATA"     TO W-FORMATO                         
                 WRITE   R-LINEA                                            
                         FORMAT          W-FORMATO                          
                         INDICATORS      IND-AREA.                          
                 DISPLAY "FILE STATUS:" FS-LINEA.                           
                 DISPLAY "DATA WRITTEN:" W-FORMATO.                         
                                                                            
                 IF FS-LINEA = "9N"                                         
                  DROP AC-PGMDEV FROM A-LINEA                               
                  ACQUIRE AC-PGMDEV FOR A-LINEA                             
                  DISPLAY "FILE STATUS:" FS-LINEA                           
                 END-IF                                                     
                 
                 READ A-LINEA                                                                   
                        INDICATORS IND-AREA.                                
                                                                            
                 IF  FS-LINEA EQUAL "00"                                    
                         MOVE    REGDATA-I     TO XX-MENSAJE.               
                 DISPLAY "FILE STATUS:" FS-LINEA.                           
                 DISPLAY "DATA READ:" XX-MENSAJE.                           
                                                                                                                                                 
                 STOP RUN.                                                  
    
    ********************************************************************
    [U][B]Output:[/B][/U]
    FILE STATUS:00       
    FILE STATUS:9N       
    DATA WRITTEN:REGDATA 
    FILE STATUS:9C       
    FILE STATUS:10

  • #2
    Re: ICF file handling in COBOL

    Hmm... Can you see something in the job log or on QSYSOPR that could help ?
    Philippe

    Comment


    • #3
      Re: ICF file handling in COBOL

      Dear Mercury,

      The JOBLOG had the following informations:

      CALL HANDYICF
      FILE STATUS:00 [output of display statement for file status of OPEN operation]
      1. "The file COMICFON2 in the library COMLIBPR has not acquired the program devices".

      FILE STATUS:9N
      DATA WRITTEN:REGDATA
      2. "Could not find the program device in the file COMICFON2 of the library COMLIBPR".

      3. "Not specified the Remote Location to the program device".

      FILE STATUS:9C
      4. No invitation pending for the file COMICFON2 in the library COMLIBPR.

      From the above informations, i understood that there is some problem with acquring the program device for the file COMICFON2.
      For your information, the file COMICFON2 has ACQPGMDEV = *NONE. Does it create some problem with this? If so, what needs to done?
      Kindly help.

      Comment


      • #4
        Re: ICF file handling in COBOL

        Originally posted by kpandian
        For your information, the file COMICFON2 has ACQPGMDEV = *NONE. Does it create some problem with this?
        I'm not very familiar with ICF file programming but I remember that the program devices matter.

        This is what I read in the ICF manual :
        If the program is written to handle the requesting program device, you must define a program device entry for the requester by specifying a special value of *REQUESTER for the RMTLOCNAME parameter on the ADDICFDEVE or the OVRICFDEVE command.

        Read the manual "ICF Programming" that you can d/l from here. Check out particularly Chapter 4.Intersystem Communications Function.
        Philippe

        Comment


        • #5
          Re: ICF file handling in COBOL

          Thanks for the information Mercury and i am going through the ICF Programming manual currently. I just have general doubt regarding the ICF file usage.
          Is it possible to WRITE some data into a ICF file from one priogram[Eg. PGM1] and reading the same from another program[Eg. PGM2] of the same server?

          Everywhere i have seen, the concept of ICF file is related with REMOTE LOCATION NAME. But, all i need is do the above said operations on a ICF file within a single server and using any REMOTE connection. Please help.

          Comment


          • #6
            Re: ICF file handling in COBOL

            Originally posted by kpandian
            Is it possible to WRITE some data into a ICF file from one priogram[Eg. PGM1] and reading the same from another program[Eg. PGM2] of the same server?
            I dont know however I guess that it should work. Make a test.
            Philippe

            Comment

            Working...
            X