HP3000-L Archives

August 1999, Week 2

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:
"Peter Chong Sr. Systems Analyst (MRP/ERP)" <[log in to unmask]>
Reply To:
Peter Chong Sr. Systems Analyst (MRP/ERP)
Date:
Tue, 10 Aug 1999 14:22:34 -0700
Content-Type:
text/plain
Parts/Attachments:
text/plain (215 lines)
Try little extra definition in COBOL working storage section.
like

01 STUDENT-IDX         PIC X(5).
01 STUDENT-ID      REDEFINES    STUDENT-IDX  PIC 9(5).

It will reserve 5 characters room in working storage area
or
01 STUDENT-ID PIC 9(5) DISP.
*    Student ID will translate to Packed array [1..5] of char in Pascal

I guess display command in COBOL force to STUDENT-ID to DISP(?).

Cheers
Peter C.
Ted Ashton <[log in to unmask]> wrote in message
news:F4B1826B1A21D211AEC5006008207AF401E2488B@dogbert.csillc.com...
> Feel free to where I should be reading in _Beyond_Risc!_ to find this . .
.
>
> I'm attempting to call CM Pascal (eventually to be a switch stub) from
> CM COBOL.  Here's the COBOL:
>
>     1     $CONTROL USLINIT
>     1.1   $CONTROL BOUNDS
>     1.2    IDENTIFICATION DIVISION.
>     1.3    PROGRAM-ID.  PTestp.
>     1.4
>     1.5    DATA DIVISION.
>     1.6    WORKING-STORAGE SECTION.
>     1.7
>     1.8    01  STUDENT-ID  PIC 9(5).
>     1.9    01  DEFAULT     PIC 9(7)V99 COMP.
>     2      01  DEPOSIT     PIC 9(7)V99 COMP.
>     2.1    01  SEM         PIC X(4).
>     2.2    01  YEAR-SEM    PIC X.
>     2.3    01  CALL-MODE   PIC 9.
>     2.4    01  WS          PIC X(4096) VALUE LOW-VALUES.
>     2.5
>     2.6    PROCEDURE DIVISION.
>     2.7
>     2.8    ONE-PARAGRAPH.
>     2.9      MOVE "F99" TO SEM.
>     3        MOVE 56015 TO STUDENT-ID.
>     3.1      MOVE 2500.00 TO DEFAULT.
>     3.2      MOVE 1500.00 TO DEPOSIT.
>     3.3      MOVE "Y" TO YEAR-SEM.
>     3.4      MOVE 1 TO CALL-MODE.
>     3.5      DISPLAY STUDENT-ID.
>     3.6      CALL "PRINTPASS" USING STUDENT-ID, DEFAULT, DEPOSIT,
>     3.7                             SEM, YEAR-SEM, CALL-MODE, WS.
>
> Here's the Pascal:
>
>     1     $Standard_Level 'HP3000'$
>     2     $SubProgram$
>     3     $List Off$
>     4     Program CM_PrintPass(Output);  { CM to NM Switch Stub }
>     5
>     6       type
>     7         int          = -32768..32767;
>     8         int_Ary32    = packed array [1..32] of int;
>     9         str80        = string[80];
>    10         pac4         = packed array[1..4] of char;
>    11         pac5         = packed array[1..5] of char;
>    12         pac16        = packed array[1..16] of char;
>    13         work_store   = packed array[1..4096] of char;
>    14         dual         = record
>    15           case integer of
>    16             1: (i  : int);
>    17             2: (p5 : pac5);
>    18             3: (p4 : pac4);
>    19             4: (c  : char);
>    20           end;
>    21
>    22     {************************************}
>    23     {  These are the Stub procedures     }
>    24     {  to be called by the CM program    }
>    25     {************************************}
>    26     Procedure PrintPass(var student_id    : dual;
>    27                         var default       : integer;
>    28                         var deposit       : integer;
>    29                         var semester      : dual;
>    30                         var year_sem      : dual;
>    31                         var mode          : dual;
>    32                         var ws            : work_store);
>    33
>    34       begin { SCDateLine switch stub }
>    35         rewrite(Output,'$STDLIST');
>    36         writeln('Here we are!');
>    37         writeln(baddress(student_id),baddress(default));
>    38
writeln(baddress(deposit),baddress(semester),baddress(year_sem));
>    39         writeln(baddress(mode),baddress(ws));
>    40         writeln(student_id.p5);
>    41         writeln(default);
>    42         writeln(deposit);
>    43         writeln(semester.p4);
>    44         writeln(year_sem.c);
>    45         writeln(mode.c);
>    46       end;  { PrintPass switch stub }
>    47
>    48     begin  { dummy outer block to satisfy syntax }
>    49     end.
>
> Here's the compile:
>
> ADMDEV.ADMIN/:cobol t1,,$null
>
> PAGE 0001   HP32233A.02.05  [85] Copyright Hewlett-Packard CO. 1989
>
>
>
> 0 ERROR(s), 0 QUESTIONABLE, 0 WARNING(s)
>
>     DATA AREA IS %004201 WORDS.
>     CPU TIME = 0:00:00.  WALL TIME = 0:00:00.
> ADMDEV.ADMIN/:pascal t2,,$null
>
> PAGE   1  HEWLETT-PACKARD   HP32106A.01.32    PASCAL/V      (C)
HEWLETT-PACKARD
>  CO. 1985  MON, AUG  9, 1999,  7:04 PM
>
>
>                       NUMBER OF ERRORS =  0     NUMBER OF WARNINGS =  0
>                       PROCESSOR TIME 0: 0: 1    ELAPSED TIME 0: 0: 0
>                       NUMBER OF LINES =   49    LINES/MINUTE =  2665.5
> End Run
> ADMDEV.ADMIN/:p
> Begin Prep
> End Prep
> ADMDEV.ADMIN/:r
>
> 56015
> Here we are!
>          212         218
>          222         226         230
>          232         117
> 56015
>       250000
>       150000
> F99
> Y
> 1
> End Run
>
> Hokey dokey, all fine and dandy, right?  Ok.  Two questions:
>   1) Why do I have to do that "dual" thing.  I know that it has to do with
>      word addresses vs. byte addresses, but I don't know much more than
that.
>      What is the right way to do what I'm doing there?
>
>   2) Watch this:
>
> ADMDEV.ADMIN/o t1
> Shut T2.ADMDEV.ADMIN
> Open T1.ADMDEV.ADMIN COBX Current = 3.7
> ADMDEV.ADMIN/l "display"
>     3.5      DISPLAY STUDENT-ID.
> 1 line found
> ADMDEV.ADMIN/c 7/7 "*"
>     3.5   *  DISPLAY STUDENT-ID.
> 1 line changed
> ADMDEV.ADMIN/:cobol t1,,$null
>
> PAGE 0001   HP32233A.02.05  [85] Copyright Hewlett-Packard CO. 1989
>
>
>
> 0 ERROR(s), 0 QUESTIONABLE, 0 WARNING(s)
>
>     DATA AREA IS %004035 WORDS.
>     CPU TIME = 0:00:00.  WALL TIME = 0:00:00.
> ADMDEV.ADMIN/:pascal t2,,$null
>
> PAGE   1  HEWLETT-PACKARD   HP32106A.01.32    PASCAL/V      (C)
HEWLETT-PACKARD
>  CO. 1985  MON, AUG  9, 1999,  7:08 PM
>
>
>                       NUMBER OF ERRORS =  0     NUMBER OF WARNINGS =  0
>                       PROCESSOR TIME 0: 0: 1    ELAPSED TIME 0: 0: 0
>                       NUMBER OF LINES =   49    LINES/MINUTE =  2665.5
> End Run
> ADMDEV.ADMIN/:p
> Begin Prep
> End Prep
> ADMDEV.ADMIN/:r
>
> Here we are!
>           12          18
>           22          26          30
>           32          17
> 01
>       250000
>       150000
> F9
>
>
> End Run
>
> What!!!?!!!  What is that DISPLAY line doing?  Why in the world does my
> program cease to function when I remove it?
>
> Thanks in advance for any enlightenment you can share,
> Ted
> --
> Ted Ashton ([log in to unmask]), Info Serv, Southern Adventist University
>           ==========================================================
> The riddle does not exist. If a question can be put at all, then it can
also
> be answered.
>                          -- Wittgenstein, Ludwig (1889-1951)
>

ATOM RSS1 RSS2