Scott,

I found this document 
http://www-01.ibm.com/support/docview.wss?uid=swg21256665&aid=1 which is some 
version of the source to EZACICTR.  In there I see that mode=single and 
mode=multiple have a different number of parameters. Your call (as below) are 
for mode=multiple, hence the parameter number error.  Also in this source, I 
see that table UK translates an incoming EBCDIC X'A1' to an ASCII X'EE'.  So 
the results in the mode=multiple example below seem to match that.

     Cliff McNeill


________________________________
From: IBM Mainframe Discussion List <IBM-MAIN@LISTSERV.UA.EDU> on behalf of 
scott Ford <idfli...@gmail.com>
Sent: Wednesday, March 7, 2018 12:19 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: Codepage

All,

This isnt a Java issue see below:


Sample program calling EZACICTR with MODE in Table set to SINGLE...

CBL NOC(E),FLAG(W),DATA(31),NODYN,RES,RENT,OPT,MAP,NOSSR
CBL NOZWB,NUM,NOTERM,NOVBREF,X,APOST,LIB,LIST,NSYMBOL(NATIONAL)
       IDENTIFICATION DIVISION.
       PROGRAM-ID. IDFNLS1.
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
       01 TRANSLATE-RC        PIC 9(8) COMP.
       01 TRANSLATE-TBLNAME   PIC X(8).
       01 REPLY-MESSAGE-SIZE  PIC S9(5) COMP VALUE 0.
       01 WS-MSG-AREA         PIC X
            VALUE '~'.
       01 HEXNUM PIC X(4).
       01 DECNUM REDEFINES HEXNUM PIC S9(8) COMP.
       01 HEXVAL PIC X(20).
       01 HEXSTR   PIC X(16) VALUE '0123456789ABCDEF'.
       01 DEC    PIC S9(4) COMP.
       01 FILLER REDEFINES DEC.
          05 FILLER PIC X.
          05 DECBYTE PIC X.
       01 I      PIC S9(8) COMP.
       01 J      PIC S9(8) COMP.
       01 Q      PIC S9(8) COMP.
       01 R      PIC S9(8) COMP.
       01 J1     PIC S9(8) COMP.
       01 Q1     PIC S9(8) COMP.
       01 R1     PIC S9(8) COMP.
       PROCEDURE DIVISION.
           MOVE 1  TO REPLY-MESSAGE-SIZE
           MOVE 'UK' TO TRANSLATE-TBLNAME
           DISPLAY '--EBCDIC-IN ----'
           DISPLAY 'TRANS-TBL   ----' TRANSLATE-TBLNAME
           DISPLAY 'REPLY-MSG-SIZE  ' REPLY-MESSAGE-SIZE
           DISPLAY 'DATA IN --      ' WS-MSG-AREA
           CALL 'EZACIE2A' USING WS-MSG-AREA REPLY-MESSAGE-SIZE
               TRANSLATE-TBLNAME
               RETURNING TRANSLATE-RC.
           DISPLAY '--ASCII-OUT ----'
           DISPLAY 'TRANSLATE-RC    ' TRANSLATE-RC
           DISPLAY 'TRANS-TBL   ----' TRANSLATE-TBLNAME
           DISPLAY 'REPLY-MSG-SIZE  ' REPLY-MESSAGE-SIZE
           DISPLAY 'DATA OUT --     ' WS-MSG-AREA
           MOVE WS-MSG-AREA TO HEXNUM
           PERFORM VARYING I FROM 1 BY 1 UNTIL I > 4
                 COMPUTE J = 2 * I - 1
                 MOVE HEXNUM(I:1) TO DECBYTE
                 DIVIDE DEC BY 16 GIVING Q REMAINDER R
                 COMPUTE  J1 = J + 1
                 COMPUTE  Q1 = Q + 1
                 COMPUTE R1 = R + 1
                 MOVE HEXSTR(Q1:1) TO HEXVAL(J:1)
                 MOVE HEXSTR(R1:1) TO HEXVAL(J1:1)
           END-PERFORM.
                 DISPLAY 'PRINTABLE HEX: ' HEXVAL.
           GOBACK.


Heres the output:

--EBCDIC-IN ----
TRANS-TBL   ----UK
REPLY-MSG-SIZE  00001
DATA IN --      ~
--ASCII-OUT ----
TRANSLATE-RC    00000012  -- this indicates wrong number of parameters
TRANS-TBL   ----UK
REPLY-MSG-SIZE  00001
DATA OUT --     ~
PRINTABLE HEX: A1404040

Second execution - EZACICTR MODE set to MULTIPLE


--EBCDIC-IN ----
TRANS-TBL   ----UK
REPLY-MSG-SIZE  00001
DATA IN --      ~
PRINTABLE HEX: A1404040
--ASCII-OUT ----
TRANSLATE-RC    00000000
TRANS-TBL   ----UK
REPLY-MSG-SIZE  00001
DATA OUT --
*PRINTABLE HEX: EE404040*


I need to whats going on so i can fix it..
The EZACICTR is a IBM supplied table...from TCPIP.SEZAINST, we should be
seeing the  * PRINTABLE HEX: A1404040*

Anyone have any ideas...

Scott


On Wed, Mar 7, 2018 at 11:37 AM Seymour J Metz <sme...@gmu.edu> wrote:

> GX20-0157-2, GX20-1850-3 and GX20-1850-36 have ~  at A1, with an alternate
> glyph of degree sign.
>
> --
> Shmuel (Seymour J.) Metz
> http://mason.gmu.edu/~smetz3
The Homepage of Shmuel (Seymour J.) Metz<http://mason.gmu.edu/~smetz3>
mason.gmu.edu
Professional. I am a senior systems programmer and software developer with 
experience on a wide variety of languages and platforms. I have participated in 
the design ...


>
> ________________________________________
> From: IBM Mainframe Discussion List <IBM-MAIN@listserv.ua.edu> on behalf
> of Charles Mills <charl...@mcn.org>
> Sent: Tuesday, March 6, 2018 1:15 PM
> To: IBM-MAIN@listserv.ua.edu
> Subject: Re: Codepage
>
> Don't confuse glyphs with code points. ~ is perhaps a delimiter for humans
> who are perceiving glyphs visually but not for software that is processing
> code points in binary. It would facilitate clearer thinking to say "we are
> using x'something' (what? My poor old yellow card does not even have ~) as
> a delimiter, and then translating that to ASCII before sending it to
> software which expects the message to be delimited with x'something'."
>
> Charles
>
>
> -----Original Message-----
> From: IBM Mainframe Discussion List [mailto:IBM-MAIN@LISTSERV.UA.EDU] On
> Behalf Of Elardus Engelbrecht
> Sent: Tuesday, March 6, 2018 9:46 AM
> To: IBM-MAIN@LISTSERV.UA.EDU
> Subject: Re: Codepage
>
> scott Ford wrote:
>
> I see that J R replied to you, but I am still really confused about your
> post. Since this is about code page, I am probably on a different [code]
> page ... (yes, yes, that was an intended crrrrrruel pun and I will not turn
> a new page, mind you... ;-D )
>
>
> >I need some help on localization for codepages. The issue is we use a '~'
> as a end of messages delimiter.
>
> Ouch.... Where is that delimiter '~' and in what code page is that? In
> EBCDIC or ASCII?
>
> ----------------------------------------------------------------------
> 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
>


--



*IDMWORKS *

Scott Ford

z/OS Dev.




“By elevating a friend or Collegue you elevate yourself, by demeaning a
friend or collegue you demean yourself”



www.idmworks.com<http://www.idmworks.com>
Home - IDMWORKS<http://www.idmworks.com/>
www.idmworks.com
Most IT Departments Are Lean And Lacking The Resources To Perform The Critical 
Tasks Of Preparing, Planning And Executing A Comprehensive Data Center 
Migration Or IT ...



scott.f...@idmworks.com

Blog: www.idmworks.com/blog<http://www.idmworks.com/blog>
[https://www.idmworks.com/wp-content/uploads/2015/06/blog-page-image.jpg]<http://www.idmworks.com/blog>

IDMWORKS Blog - IDMWORKS<http://www.idmworks.com/blog>
www.idmworks.com
I worked with a client that had too many open process tasks in OIM. This had 
occurred as the result of a combination of network issues and the surprise 
retirement of an application. This resulted in thousands of process tasks stuck 
in a rejected status. Since the application had been retired, many of the tasks 
could not … Continue reading Bulk Open Task Cleanup







*The information contained in this email message and any attachment may be
privileged, confidential, proprietary or otherwise protected from
disclosure. If the reader of this message is not the intended recipient,
you are hereby notified that any dissemination, distribution, copying or
use of this message and any attachment is strictly prohibited. If you have
received this message in error, please notify us immediately by replying to
the message and permanently delete it from your computer and destroy any
printout thereof.*

----------------------------------------------------------------------
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

Reply via email to