Re: Q re attaching COBOL program

2013-03-20 Thread Shmuel Metz (Seymour J.)
In <8646586792164199.wa.victor.gilbroadridge@listserv.ua.edu>, on
03/19/2013
   at 10:48 AM, Victor Gil  said:

>Answering my own question [for the archives] - LE expects a COBOL
>MAIN entry [subtasked or not] to be invoked via the "EXEC PARM=..."
>convention.

That convention is that the first (only) parameter address points to a
halfword length followed by a character string. That doesn't match
what you posted. What is the full second parameter that you are
passing to your assembler subroutine?

-- 
 Shmuel (Seymour J.) Metz, SysProg and JOAT
 Atid/2
We don't care. We don't have to care, we're Congress.
(S877: The Shut up and Eat Your spam act of 2003)

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Victor Gil
Joe, thanks for the post.

When a caller calls COB#SYNC it indeed passes 2 parms, but the first one is 
just a name of the program to attach, so it's internal to COB#SYNC logic.

The second parm is the one actually passed to the subtask on the ATTACH, so it 
does match the PROCEDURE USING on the callee.  As was explained in a prior post 
such parm has to conform to the EXEC PARM='...' convention.

-Victor-  


Hello:  When a COBOL CALL or ENTRY is compiled, each item in the USING is used 
to create code to process a parameter list of full words equal in number to the 
number of items in that USING clause.  So the CALL parameter list will have two 
full words.  The ENTRY code will only process one full word.  

So, the CALL to COB#SYNC builds two fullwords of addresses, but the PROCEDURE 
DIVISION USING is only going to load one BLL cell.  The BLL cell for item 
TPTAPI-COMMAREA will be loaded with the address of the caller's item WS-TPTAPI. 
 The second item WS-TPTAPI-COMMAREA is not addressible by the subroutine 
(unless the second item is contiguous in storage to WS-TPTAPI and the 
TPTAPI-COMMAREA item describes both areas, a somewhat unorthodox way of passing 
parameters).

I would have coded two items in the subroutines ENTRY USING clause. 

CALL-TPTAPI.   
 
DISPLAY WS-TPTAPI-COMMAREA   
CALL "COB#SYNC"  USING WS-TPTAPI 
   WS-TPTAPI-COMMAREA.   
  -  -  -  -  -  -  -  -  -  -  -  -  -  2 Line(s) no
DISPLAY WS-TPTAPI-COMMAREA.  


The subroutine's PROCEDURE USING:

PROCEDURE DIVISION USING TPTAPI-COMMAREA. 

regards, Joe D'Alessandro

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Joe D'Alessandro
Hello:  When a COBOL CALL or ENTRY is compiled, each item in the USING is used 
to create code to process a parameter list of full words equal in number to the 
number of items in that USING clause.  So the CALL parameter list will have two 
full words.  The ENTRY code will only process one full word.  

So, the CALL to COB#SYNC builds two fullwords of addresses, but the PROCEDURE 
DIVISION USING is only going to load one BLL cell.  The BLL cell for item 
TPTAPI-COMMAREA will be loaded with the address of the caller's item WS-TPTAPI. 
 The second item WS-TPTAPI-COMMAREA is not addressible by the subroutine 
(unless the second item is contiguous in storage to WS-TPTAPI and the 
TPTAPI-COMMAREA item describes both areas, a somewhat unorthodox way of passing 
parameters).

I would have coded two items in the subroutines ENTRY USING clause. 

CALL-TPTAPI.   
 
DISPLAY WS-TPTAPI-COMMAREA   
CALL "COB#SYNC"  USING WS-TPTAPI 
   WS-TPTAPI-COMMAREA.   
  -  -  -  -  -  -  -  -  -  -  -  -  -  2 Line(s) no
DISPLAY WS-TPTAPI-COMMAREA.  


The subroutine's PROCEDURE USING:

PROCEDURE DIVISION USING TPTAPI-COMMAREA. 

regards, Joe D'Alessandro

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Victor Gil
Answering my own question [for the archives] - LE expects a COBOL MAIN entry 
[subtasked or not] to be invoked via the "EXEC PARM=..." convention.

So, in the Assembler middleman I had to take the original pointer in R1 and 
save it as the only passing parm in an EXEC_PARMS area, then Attach with R1 
pointing to A(EXEC_PARMS).  The opposite conversion into the CALL  USING 
 format is taking place in the COBOL MAIN stub.  Unfortunately, the 
COBOL stub needs to know the NUMBER of such parameters to be able to issue a 
respective CALL, so for now I am settling just for one such parm.

-Victor-

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread David Crayford

On 19/03/2013 10:05 PM, Paul Gilmartin wrote:

On Tue, 19 Mar 2013 21:50:15 +0800, David Crayford wrote:

Doesn't task termination automatically free some resources that
the programmer would need to free specifically after a LINK?

Also if the attached program abends it doesn't sink the entire ship.


I suspect that can be covered with an ESTAE in either case.  But it's
easier with ATTACH.

It's certainly easier when you don't *own* the attached program, which
is usually when I've seen this technique used.


I know some programmers worry (excessively?) about task overhead,
even to the extent of developing alternatives (JES? CICS?), or keeping
a stable of idle tasks to be dispatched when needed.  I think there are
better uses for development resources.



I'm not quite sure if I understand what your point is Paul. Are you 
saying that a task (thread) pool scheduler is a bad design?





-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Paul Gilmartin
On Tue, 19 Mar 2013 21:50:15 +0800, David Crayford wrote:
>
 Doesn't task termination automatically free some resources that
 the programmer would need to free specifically after a LINK?
>>> Also if the attached program abends it doesn't sink the entire ship.
>>>
>> I suspect that can be covered with an ESTAE in either case.  But it's
>> easier with ATTACH.
>
>It's certainly easier when you don't *own* the attached program, which
>is usually when I've seen this technique used.
> 
I know some programmers worry (excessively?) about task overhead,
even to the extent of developing alternatives (JES? CICS?), or keeping
a stable of idle tasks to be dispatched when needed.  I think there are
better uses for development resources.

-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread David Crayford

On 19/03/2013 9:27 PM, Paul Gilmartin wrote:

On Tue, 19 Mar 2013 21:08:03 +0800, David Crayford wrote:


On 19/03/2013 9:01 PM, Paul Gilmartin wrote:

On Tue, 19 Mar 2013 06:49:00 -0500, Tom Marchant wrote:

I'm just curious.  Why do you need to ATTACH the program
if it is not to run asynchronously?


Doesn't task termination automatically free some resources that
the programmer would need to free specifically after a LINK?

Also if the attached program abends it doesn't sink the entire ship.


I suspect that can be covered with an ESTAE in either case.  But it's
easier with ATTACH.


It's certainly easier when you don't *own* the attached program, which 
is usually when I've seen this technique used.



-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Paul Gilmartin
On Tue, 19 Mar 2013 21:08:03 +0800, David Crayford wrote:

>On 19/03/2013 9:01 PM, Paul Gilmartin wrote:
>> On Tue, 19 Mar 2013 06:49:00 -0500, Tom Marchant wrote:
>>> I'm just curious.  Why do you need to ATTACH the program
>>> if it is not to run asynchronously?
>>>
>> Doesn't task termination automatically free some resources that
>> the programmer would need to free specifically after a LINK?
>
>Also if the attached program abends it doesn't sink the entire ship.
> 
I suspect that can be covered with an ESTAE in either case.  But it's
easier with ATTACH.

-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Victor Gil
Because these programs connect to DB2 using *different* front ends for 
call-attachment facility [not to mention different DB2 plans and different ways 
the plan names are determined during run time].  So, each program essentially 
needs its own DB2 connection.

-Victor-


===
I'm just curious.  Why do you need to ATTACH the program 
if it is not to run asynchronously?

-- 
Tom Marchant

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread David Crayford

On 19/03/2013 9:01 PM, Paul Gilmartin wrote:

On Tue, 19 Mar 2013 06:49:00 -0500, Tom Marchant wrote:

I'm just curious.  Why do you need to ATTACH the program
if it is not to run asynchronously?


Doesn't task termination automatically free some resources that
the programmer would need to free specifically after a LINK?


Also if the attached program abends it doesn't sink the entire ship.



-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Paul Gilmartin
On Tue, 19 Mar 2013 06:49:00 -0500, Tom Marchant wrote:
>
>I'm just curious.  Why do you need to ATTACH the program 
>if it is not to run asynchronously?
> 
Doesn't task termination automatically free some resources that
the programmer would need to free specifically after a LINK?

-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-19 Thread Tom Marchant
On Mon, 18 Mar 2013 15:29:47 -0500, Victor Gil wrote:

>We have a need to call a COBOL subroutine by attaching 
>it as a subtask, so the call is done through an Assembler 
>stub that issues the Attach, Waits on the termination ECB 
>and Detaches the subtask.

I'm just curious.  Why do you need to ATTACH the program 
if it is not to run asynchronously?

-- 
Tom Marchant

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-18 Thread Victor Gil
Well, if you're anxious to see the code, here it is -

COB#SYNC ATENTRY 'Run ASYNC task from COBOL',TRACE=NO
*   
 ST   R1,R1_ON_ENTRY
*   
 LA   R4,DYN_PCT
   USING MTCT_TASK,R4   
 LR5,0(,R1)  <-- FIRST PARM = PROGRAM NAME  
 MVC  MTCT_TASK_PROG,0(R5) 
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - 10 Line(s) not Displayed 
 MVC  DYN_ATCH(L_ATCH_LST),ATCH_LST 
 XC   MTCT_TASK_TECB,MTCT_TASK_TECB 
 LA   R2,MTCT_TASK_TECB 
 LA   R15,DYN_ATCH  
 LA   R1,4(0,R1)  PASS THE REST OF PARMS
*   
 ATTACH EPLOC=MTCT_TASK_PROG,  X
   ECB=(R2),   X
   SZERO=NO,   X
   SF=(E,(R15)) 
*   
 LTR  R15,R15 DID ATTACH WORK?  
 BZ   ATTACHEDYES - 
   LOG$MSG 'Unable to Attach . Abending...',MTCT_TASK_PROG  
 DC  H'0'   
*   
ATTACHED DC 0H  
 STR1,MTCT_TASK_TCB   SAVE TCB  
 UNPK  DWORK(9),MTCT_TASK_TCB(5)
 MVZ   DWORK,ZONE_ZERO  
 TRDWORK,HEXTAB 
LOG$MSG 'Prog  Attached. TCB=',X
   MTCT_TASK_PROG,DWORK 
*   
 LA   R2,MTCT_TASK_TECB 
 WAIT 1,ECB=(R2)
*   
LOG$MSG 'Prog  terminated',MTCT_TASK_PROG   
*   
DETACH  MTCT_TASK_TCB   
*   
 B   COB#SYNC_EXIT   


The call in COBOL caller follows. Notice that the commarea gets displayed 
before and after the call [this is how we know that the response is NOT passed 
back] 

CALL-TPTAPI. 
 
DISPLAY WS-TPTAPI-COMMAREA   
CALL "COB#SYNC"  USING WS-TPTAPI 
   WS-TPTAPI-COMMAREA.   
  -  -  -  -  -  -  -  -  -  -  -  -  -  2 Line(s) no
DISPLAY WS-TPTAPI-COMMAREA.  


The subroutine's PROCEDURE USING:

PROCEDURE DIVISION USING TPTAPI-COMMAREA.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-18 Thread Steve Comstock

On 3/18/2013 4:36 PM, Victor Gil wrote:

As I said, the subroutine response via a field in the passed comarea.
The commarea is just ONE parm and the resopnse field is part of the commarea, 
not the RETURN REGISTER

03  TPTAPI-RETURN-PARAMETERS.
 05  TPTAPI-RETURN-CODE   PIC  X(02).
 88  TPTAPI-SUCCESSFULVALUE '00'.
 88  TPTAPI-WARNING   VALUE '04'.
 88  TPTAPI-INVALID-PARM  VALUE '08'.


-Victor-


Hey, chill, man.

You still have not given us enough info.

1. show us your ATTACH(X) invocation
2. show us the code where your Assembler routine is looking at the return value
3. show us your procedure division header
4. show us where your COBOL program sets the return code

we may need more to see the problem, but this is a start

(and, no, LE is not making local copies of your parameter).


--

Kind regards,

-Steve Comstock
The Trainer's Friend, Inc.

303-355-2752
http://www.trainersfriend.com

* To get a good Return on your Investment, first make an investment!
  + Training your people is an excellent investment

* Try our tool for calculating your Return On Investment
for training dollars at
  http://www.trainersfriend.com/ROI/roi.html

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-18 Thread Victor Gil
As I said, the subroutine response via a field in the passed comarea.
The commarea is just ONE parm and the resopnse field is part of the commarea, 
not the RETURN REGISTER

03  TPTAPI-RETURN-PARAMETERS.   
05  TPTAPI-RETURN-CODE   PIC  X(02).
88  TPTAPI-SUCCESSFULVALUE '00'.
88  TPTAPI-WARNING   VALUE '04'.
88  TPTAPI-INVALID-PARM  VALUE '08'.


-Victor-

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: Q re attaching COBOL program

2013-03-18 Thread Steve Comstock

On 3/18/2013 2:29 PM, Victor Gil wrote:

We have a need to call a COBOL subroutine by attaching it as a subtask, so
the  call is done through an Assembler stub that issues the Attach, Waits on the

termination ECB and Detaches the subtask.


The subroutine gets the parms, does what it's job and returns back with an
RCfield which is a part of the passed structure.

However, the caller *does not* see this RC!

Is the LE making a local copy of the parms? And if yes - how to workaround this 
issue?

TIA,
-Victor-



Sounds like you possiblye are not passing and receiving the structure
in the same way.

If your COBOL program is moving the return code value into
the RC field in your structure, but on return you do not
see the value: are you passing by reference or by content?
are you receiving by reference or by content?

On the other hand, if your COBOL program is just setting
the RETURN-CODE special register, that value is not passed
back in your passed structure automatically.

So it would help to see some code: how your Assembler routine
sets up the passed parms and how it examines these after the
CALL; then how your COBOL routine sees the passed parms (show
us the linkage section, the using statement, and the point in
the code where you think RC is getting set.



--

Kind regards,

-Steve Comstock
The Trainer's Friend, Inc.

303-355-2752
http://www.trainersfriend.com

* To get a good Return on your Investment, first make an investment!
  + Training your people is an excellent investment

* Try our tool for calculating your Return On Investment
for training dollars at
  http://www.trainersfriend.com/ROI/roi.html

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Q re attaching COBOL program

2013-03-18 Thread Victor Gil
We have a need to call a COBOL subroutine by attaching it as a subtask, so the 
call is done through an Assembler stub that issues the Attach, Waits on the 
termination ECB and Detaches the subtask.

The subroutine gets the parms, does what it's job and returns back with an RC 
field which is a part of the passed structure.

However, the caller *does not* see this RC!

Is the LE making a local copy of the parms? And if yes - how to workaround this 
issue?

TIA,
-Victor-  

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN