HP3000-L Archives

March 2003, Week 1

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Ken Hirsch <[log in to unmask]>
Reply To:
Ken Hirsch <[log in to unmask]>
Date:
Fri, 7 Mar 2003 14:03:22 -0500
Content-Type:
text/plain
Parts/Attachments:
text/plain (122 lines)
You need to pass sd-2 and size-addr by value
    call "CONNECT" using \sd-2\ addr \size-addr\
        giving result-code.

----- Original Message -----
From: "Feldmann, Rick" <[log in to unmask]>
To: <[log in to unmask]>
Sent: Friday, March 07, 2003 1:46 PM
Subject: [HP3000-L] COBOL and BSD Sockets


> Help - Does anyone see anything wrong with this COBOL program.  The call
to
> CONNECT always fails.
>
>  IDENTIFICATION DIVISION.
>
>  PROGRAM-ID.  SOCKCL.
>  DATE-COMPILED.
>
>  ENVIRONMENT DIVISION.
>  CONFIGURATION SECTION.
>
>  data division.
>  WORKING-STORAGE SECTION.
>  01  af-inet                    pic s9(9) binary value 2.
>  01  sock-stream                pic s9(9) binary value 1.
>  01  proto                      pic s9(9) binary value 0.
>  01  socket-info.
>      05  sd-2                   pic s9(9) comp.
>      05  ext-ip-addr            pic x(16).
>      05  int-ip-addr-x.
>          10  int-ip-addr        pic s9(9) comp.
>  01  result-code                pic s9(9) binary.
>  01  size-addr                  pic s9(9) binary value 16.
>  01  errno                      pic s9(9) binary external.
>  01  ip-addr                    pic x(16) value "".
>  01  addr.
>      03  filler                 pic s9(4) binary value 2.
>      03  addr-port              pic s9(4) binary value 0.
>      03  addr-ip-addr           pic s9(9) binary value 0.
>      03  filler                 pic x(8) value low-values.
>
>  01  MSG-BUFF                   pic x(9) value "".
>  01  RETURN-MSG                 pic x(20) value spaces.
>
>  01  bytes-sent                 pic s9(9) comp value 0.
>  01  bytes-received             pic s9(9) comp value 0.
>
>  PROCEDURE DIVISION.
>  000-start.
>    perform 100-open-socket.
>    perform 200-talk.
>    perform 300-wrap-up.
>    stop run.
>
>  100-open-socket.
>    move spaces to ip-addr, MSG-BUFF
>    display "Enter IP Address : " with no advancing.
>    accept ip-addr.
>    display "Enter Message : " with no advancing.
>    accept MSG-BUFF.
>    call "SOCKET" using \af-inet\ \sock-stream\ \proto\
>        giving sd-2.
>    if sd-2 = -1
>        display "SOCKET failed; ERRNO=" errno
>    else
>        display "SOCKET called successfully".
>
>    call "INET_ADDR" using ip-addr giving addr-ip-addr.
>    if addr-ip-addr = -1
>        display "INET-ADDR failed"
>    else
>        display "INET-ADDR called successfully".
>
>    move 0 to result-code.
>    add 4321 to addr-port.
>    call "CONNECT" using sd-2 addr size-addr
>        giving result-code.
>    display "IP addr : ", ip-addr.
>    display "SID     : ", sd-2.
>    display "Port is : ", addr-port.
>    display "IP is   : ", addr-ip-addr.
>    display "Result  : ", result-code.
>    if result-code = -1
>        display "CONNECT failed; ERRNO=" errno
>    else
>        display "CONNECT called successfully . . .".
>
>  200-talk.
>    call "SEND" using \sd-2\, MSG-BUFF, \9\, \0\
>        giving bytes-sent.
>    if bytes-sent <> 1
>        display "SEND failed; ERRNO=" errno.
>
>    call "RECV" using \sd-2\, RETURN-MSG, \20\, \0\
>        giving bytes-received.
>    if bytes-received < 1
>        display "RECV failed; ERRNO=" errno
>    else
>        display RETURN-MSG.
>
>  300-wrap-up.
>     call "SCLOSE" using \sd-2\.
>
> Thanks,
> Rick Feldmann
>
> Confidentiality Notice: This e-mail message, including any attachments, is
> for the sole use of the intended recipient/recipients and may contain
> confidential and privileged information. Any unauthorized review, use,
> disclosure or distribution is prohibited. If you are not the intended
> recipient, please contact the sender by reply e-mail and destroy all
copies
> of the original message.
>
> * To join/leave the list, search archives, change list settings, *
> * etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

ATOM RSS1 RSS2