Terry Sambrooks wrote:
Hi Folks,

I am in need of some direction from this august body.

As a bit of fun I am trying to mimic the TSO SUBMIT command available in
REXX, by using BPXWDYN in a COBOL program to dynamically allocate an FTINCL
output file and write it to the internal reader.

Do you mean an "FTINCL _input_ file"?




The first BPXWDYN to allocate the FTINCL disk data set works a treat, i.e.
RC = 0000.

The second BPXWDYN which attempts to allocate the output to the internal
reader fails with either rc=0025 or 002M (i.e. -24).

I will admit to not having experimented with the OUTDES component yet, but
am wondering whether this is actually possible given the BPXWDYN does not
have the full capability of TSO ALLOC, at least that is implied in the
manual. The COBOL Working Storage elements are: 01 ALLOC-FT-JOB. 03 FILLER PIC X(30) VALUE 'ALLOC FI(JOBIN) SHR MSG(2) DA('. 03 FT-JOB-DSN PIC X(45) VALUE SPACES. 01 ALLOC-JES-JOB. 03 FILLER PIC X(38) VALUE 'ALLOC FI(JOBOUT) WRITER(INTRDR) MSG(2)'.
Kind regards - Terry

Terry Sambrooks
Director
KMS-IT Limited
228 Abbeydale Road South
Dore, Sheffield, S17 3LA, UK

You haven't shown your procedure division call of BPXWDYN.

In our new 2-day course "Writing z/OS CGIs in COBOL", we
tackle the problem of having a user request a job and a
parm string, then we allocate the input JCL and an output
file to intrdr, copy the input file to the output, substituting
the parm string at the appropriate time (among other interesting
tasks)

http://www.trainersfriend.com/UNIX_and_Web_courses/uc04descr.htm


It looks to me like you haven't allowed for the fact the input
to a call to BPXWDYN from a COBOL program uses a half-word
prefixed string. Here are some excerpts from the submit-a-job
lab solution from the course:

.
.
.
 File-control.
     Select jobin assign to jobin
        file status is job-in-stat.

     Select jobout assign to jobout
        file status is job-out-stat.

 Data division.
 File section.
 FD  jobin.
 01  jobin-rec         pic x(80).

 FD  jobout.
 01  jobout-rec        pic x(80).
.
.
.
 Working-storage section.

* items used in file alloation and processing  ------

 01  bpxwdyn          pic  x(8)  value 'BPXWDYN'.

 01  alloc1.
     02                pic s9(4) binary value 50.
     02                pic x(40)
             value 'alloc fi(jobin) shr dsn(scomsto.tr.cntl('.
     02  ddin          pic x(10) value spaces.

 01  alloc2.
     02                pic s9(4) binary value 66.
     02                pic x(40)
             value 'alloc fi(jobout) sysout writer(intrdr) '.
     02                pic x(26)
             value 'recfm(f) lrecl(80) msg(2) '.

 01  free-in.
     02                pic s9(4) binary value 22.
     02                pic x(22) value 'free fi(jobin)'.

 01  free-out.
     02                pic s9(4) binary value 22.
     02                pic x(22) value 'free fi(jobout)'.

 01  job-out-stat      pic 99.
 01  job-in-stat       pic 99.
.
.
.
 *   Allocate and OPEN files
 *

  file-setup.

      call bpxwdyn using alloc1
      if return-code = 0
           open input jobin
           if job-in-stat = 00
              continue
           else
              display '<h2>OPEN failed; code: '
                           job-in-stat '</h2>'
              perform html-end
              goback
           end-if
      else
        display '<h2>Allocation of input file failed; code: '
                     return-code '</h2>'
        perform html-end
        goback
      end-if

      call bpxwdyn using alloc2
      if return-code = 0
           open output jobout
           if job-out-stat = 00
              continue
           else
              display '<h2>OPEN failed; code: '
                           job-out-stat '</h2>'
              perform html-end
              goback
           end-if
      else
        display '<h2>Allocation of output file failed; code: '
                     return-code '</h2>'
        perform html-end
        goback
      end-if

... and lots more ...

Works fine.



Other techniques covered in this exciting course:

* emiting HTML to stdout using DISPLAY, printf, and calling
  BPX1WRT

* Redirecting to an alternate page

* Accessing environment variables; displaying environment variables

* Handling GET requests

* Dynamically building HTML responses using data from a VSAM file

* Dynamically building HTML responses using data from a DB2 table

* Creating and handling hidden controls and cookies

* Handling POST requests

* Saving files in the HFS

* Emitting Unicode

and, of course,

* Submitting jobs




Kind regards,

-Steve Comstock
The Trainer's Friend, Inc.

303-393-8716
http://www.trainersfriend.com

  z/OS Application development made easier
    * Our classes include
       + How things work
       + Programming examples with realistic applications
       + Starter / skeleton code
       + Complete working programs
       + Useful utilities and subroutines
       + Tips and techniques

==> Ask about being added to our opt-in list:              <==
==>   * Early announcement of new courses                  <==
==>   * Early announcement of new techincal papers         <==
==>   * Early announcement of new promotions               <==


----------------------------------------------------------------------
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html

Reply via email to