HP3000-L Archives

December 2003, 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:
Tad Bochan <[log in to unmask]>
Reply To:
Date:
Thu, 11 Dec 2003 17:23:29 +0100
Content-Type:
text/plain
Parts/Attachments:
text/plain (181 lines)
 >>Here's my test program.  I'm just wondering what the @4 means when it
>>displays the value of long-nbr - which you say is an address.  I'd have
>>expected some large value pointing to an area of memory like I'd get in
C.

Hi,
You are displaying long-nbr as a character string, not as a number,
so, "@4" is probably  0x40340000, which, according to my calculations
is the floating point representation of 7.
HTH

FYI,
Here is a bit of Cobol to to convert an Integer to a Real for use in
"pause".
(The code doesnt handle negative numbers)

   move 5 to IntegerValue
   call "IntegerToReal" using IntegerValue giving RealValue
   call "PAUSE" using RealValue
   where both  IntegerValue and RealValue are 'binary pic s9(9)'

$CONTROL SUBPROGRAM
 IDENTIFICATION DIVISION.
 PROGRAM-ID.  IntegerToReal.
 environment division.
 configuration section.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  filler.
  03 strg                display pic x(16).
  03 hpstatus            binary  pic s9(9).
  03 seconds             binary  pic s9(9).
  03 exponent            binary  pic s9(9).
  03 fraction            binary  pic s9(9).
 LINKAGE SECTION.
 01  interval            binary  pic s9(9).

 PROCEDURE DIVISION      using   interval.
 PauseTime.
     move     interval  to seconds
     multiply %40000000 by exponent
     move  zero    to  exponent
     move  seconds to fraction
     perform until fraction >= %40000000
        add 1 to exponent
        add fraction to fraction
     end-perform
     subtract %40000000 from fraction giving fraction
     subtract exponent  from 150      giving exponent
     multiply exponent  by %40000000  giving exponent
     add      exponent  to fraction   giving return-code
     continue.
 end-PauseTime.
     goback.
     end program IntegertoReal.





Internet
[log in to unmask]@RAVEN.UTC.EDU - 11/12/2003 11:33


Veuillez répondre à [log in to unmask]

Envoyé par :      [log in to unmask]

Pour : HP3000-L

cc :


Objet :     Re: HPEXTIN - how does it work?


 Here's my test program.  I'm just wondering what the @4 means when it
displays the value of long-nbr - which you say is an address.  I'd have
expected some large value pointing to an area of memory like I'd get in
C.

      *$CONTROL DYNAMIC
       IDENTIFICATION DIVISION.
       PROGRAM-ID.                      JRCHPEXTIN.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.

       01 INPUT-STRING                       PIC -(18)9.
       01 WIDTHX                             PIC S9(4)  COMP.
       01 BIN-NBR                            PIC S9(18) COMP.
       01 LONG-NBR                           PIC X(8).
       01 REAL-NBR                           PIC X(4).
       01 PLACES                             PIC S9(4)  COMP.
       01 ERR-FLAG                           PIC S9(4)  COMP.
       01 SCALE                              PIC S9(4)  COMP
                                             VALUE 0.
       01 RETURN-TYPE-LONG                   PIC S9(4)  COMP
                                             VALUE -2.
       01 RETURN-TYPE-REAL                   PIC S9(4)  COMP
                                             VALUE 1.
       01 BLANK-FLAG                         PIC S9(4)  COMP
                                             VALUE 1.

       01 PAUSE-TIME                         PIC 9(17)9  COMP
                                             VALUE 200.
       01 PAUSE-REAL                         PIC S9(9)  COMP
                                             VALUE 0.
       01 PAUSE-DEC                          PIC 9(4)  COMP
                                             VALUE 1.
       01 PAUSE-RESULT                       PIC 9(4)  COMP
                                             VALUE 0.

       PROCEDURE DIVISION.

       Main Section.

           MOVE PAUSE-TIME TO BIN-NBR.
           MOVE PAUSE-REAL TO LONG-NBR.
           MOVE PAUSE-DEC  TO PLACES.
           MOVE PAUSE-RESULT TO ERR-FLAG.

           DISPLAY "PAUSE TIME = " PAUSE-TIME.
           DISPLAY "PAUSE REAL = " PAUSE-REAL.
           DISPLAY "PAUSE DEC  = " PAUSE-DEC.


           MOVE BIN-NBR    TO INPUT-STRING.
           MOVE 19         TO WIDTHX.

           CALL "HPEXTIN" USING @INPUT-STRING
                                WIDTHX
                                \PLACES\
                                \RETURN-TYPE-LONG\
                                \SCALE\
                                \BLANK-FLAG\
                                LONG-NBR
                                ERR-FLAG.

           MOVE LONG-NBR TO PAUSE-REAL.
           MOVE ERR-FLAG TO PAUSE-RESULT.

           DISPLAY "CALC PAUSE REAL = " PAUSE-REAL.
           DISPLAY "PAUSE RESULT    = " PAUSE-RESULT.
           display ">" long-nbr "<".

           Exit Program.
           Stop run.



--
http://www.beluga.freeserve.co.uk

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






This message and any attachments (the "message") is intended solely for the addressees and is confidential. 
If you receive this message in error, please delete it and immediately notify the sender. Any use not in accord with 
its purpose, any dissemination or disclosure, either whole or partial, is prohibited except formal approval. 
The internet can not guarantee the integrity of this message. BNP PARIBAS (and its subsidiaries) shall (will) not 
therefore be liable for the message if modified. 

                ---------------------------------------------

Ce message et toutes les pieces jointes (ci-apres le "message") sont etablis a l'intention exclusive de ses 
destinataires et sont confidentiels. Si vous recevez ce message par erreur, merci de le detruire et d'en avertir 
immediatement l'expediteur. Toute utilisation de ce message non conforme a sa destination, toute diffusion 
ou toute publication, totale ou partielle, est interdite, sauf autorisation expresse. L'internet ne permettant pas 
d'assurer l'integrite de ce message, BNP PARIBAS (et ses filiales) decline(nt) toute responsabilite au titre de ce 
message, dans l'hypothese ou il aurait ete modifie.

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

ATOM RSS1 RSS2