Just curious if you or Jon were able to see the same behavior?  
   Embedded sql in COBOL is a huge luxury IMO. 
   If there’s a limitation using it while in an ILE bound module or srvpgm
   implementation, I really think IBM should know about it. 
   I’ll be happy to submit the PMR. 
   Jay
     On Apr 10, 2023, at 1:15 PM, Jay Vaughn <jeffersonvaughn@xxxxxxxxx>
     wrote:
     
     here is the whole thing Richard...
     remember this is a *module put into a *srvpgm called from a SQLRPGLE
     *PGM
     again, this works fine (passing parms and all) when the exec sql is
     commented out...
     PROCESS NOMONOPRC.                    
     IDENTIFICATION DIVISION.              
     PROGRAM-ID.  CBL00000M_PGM1.        
     **************************************************************
      ENVIRONMENT DIVISION.                                        
     **************************************************************
      CONFIGURATION SECTION.                                      
      SPECIAL-NAMES.                                               
     **************************************************************
      DATA DIVISION.                                              
     **************************************************************
      WORKING-STORAGE SECTION.                                               
                
      77  WS-MESSAGE          PIC X(50).                          
                                                                  
      LINKAGE SECTION.                                            
     *01 INCOMING-PARM.                                            
      01 INCOMING-VALUE1          PIC X(5).                        
      01 OUTGOING-VALUE1          PIC X(50).                       
                                                            
          exec sql                                          
            set option                                      
            commit = *NONE,                                
            closqlcsr = *ENDMOD,                            
            datfmt    = *ISO                                
          end-exec.                                        
                                                            
          exec sql                                          
            include sqlca                                  
          end-exec.                         
     **************************************************************  
      PROCEDURE DIVISION USING INCOMING-VALUE1, OUTGOING-VALUE1.    
     **************************************************************  
      main-proc.                                                    
                                                                    
         exec sql                                                  
             select "SQL row count from CBL00000M_PGM1 SQL: " concat
                    char(count(*))                                  
             into :WS-MESSAGE                                      
             from xxx.xxx                              
         end-exec.                                                  
          move ws-message to outgoing-value1.     
                        
      *   MOVE "SUCCESSFUL CALL TO CBL00000M_PGM1" TO OUTGOING-VALUE1
          EXIT PROGRAM.                                              
                     
        
     On Mon, Apr 10, 2023 at 12:12 PM Richard Schoen
     <[1]richard@xxxxxxxxxxxxxxxxx> wrote:
       This doesn't compile.
       Error: SQL7013  30          DATA DIVISION not found in source
       program.   
       Is this the full listing for the COBOL program ?
       Can you share the whole listing ?
       Regards,
       Richard Schoen
       Web: [2]
http://www.richardschoen.net
       Email: [3]richard@xxxxxxxxxxxxxxxxx
       -----------------------------
       message: 2
       date: Mon, 10 Apr 2023 08:43:57 -0400
       from: Jay Vaughn <[4]jeffersonvaughn@xxxxxxxxx>
       subject: [COBOL400-L] sqlcblle - pointer error on select into?
       I have a simple cobol sql pgm.
       I have the following pieces...
       WORKING-STORAGE SECTION.
       01  WS-MESSAGE    PIC X(50).
        LINKAGE SECTION.
       01 INCOMING-VALUE1          PIC X(5).
       01 OUTGOING-VALUE1          PIC X(50).
       **************************************************************
        PROCEDURE DIVISION USING INCOMING-VALUE1, OUTGOING-VALUE1.
       **************************************************************
        main-proc.
            exec sql
                select 'Row count from CBL00000M_PGM1 SQL: ' concat
                       char(count(*))
                into :ws-message
                from xxx.zzz
            end-exec.
            move ws-message to outgoing-value1.
            EXIT PROGRAM.
       I am getting a pointer error when it tries to exec the sql under
       main-proc.
       Why is that?
       tia
       jay
       --
       This is the COBOL Programming on the IBM i (AS/400 and iSeries)
       (COBOL400-L) mailing list
       To post a message email: [5]COBOL400-L@xxxxxxxxxxxxxxxxxx
       To subscribe, unsubscribe, or change list options,
       visit: [6]
https://lists.midrange.com/mailman/listinfo/cobol400-l
       or email: [7]COBOL400-L-request@xxxxxxxxxxxxxxxxxx
       Before posting, please take a moment to review the archives
       at [8]
https://archive.midrange.com/cobol400-l.
References
   Visible links
   1. mailto:richard@xxxxxxxxxxxxxxxxx
   2. 
http://www.richardschoen.net/
   3. mailto:richard@xxxxxxxxxxxxxxxxx
   4. mailto:jeffersonvaughn@xxxxxxxxx
   5. mailto:COBOL400-L@xxxxxxxxxxxxxxxxxx
   6. 
https://lists.midrange.com/mailman/listinfo/cobol400-l
   7. mailto:COBOL400-L-request@xxxxxxxxxxxxxxxxxx
   8. 
https://archive.midrange.com/cobol400-l
 
As an Amazon Associate we earn from qualifying purchases.