HP3000-L Archives

June 2004, 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:
Mike Hornsby <[log in to unmask]>
Reply To:
Mike Hornsby <[log in to unmask]>
Date:
Thu, 10 Jun 2004 10:05:47 -0400
Content-Type:
text/plain
Parts/Attachments:
text/plain (103 lines)
>squeeze out every last drop of 'oomph' from the 3k, we're reviewing some of the existing programs to see if we 
>can do anything to increase their performance. 

One method to tune a program is to use the PROCTIME intrinsic. This yields the total process CPU milliseconds to this point in time. If you trap the before and after PROCTIMEs into a DELTA time, and accumulate the DELTA time, you can track the total CPU required for a given section of code. The code example attached shows the CPU required in the DBGET portion of the program. 


Mike Hornsby Co-founder/Chief Technical Officer
Beechglen Development Inc. (beechglen.com)
513-922-0509 [log in to unmask]

 


:RUN MAIN
BASE>DBNAME
DETAIL SET NAME>DATA

END OF FILE                                                                     

DBGET MSECS=    000001571
TOTAL CPU MSECS=000001867

END OF PROGRAM



001000$CONTROL USLINIT
001100 IDENTIFICATION DIVISION.
001200 PROGRAM-ID. MAIN.
001300 ENVIRONMENT DIVISION.
001400 CONFIGURATION SECTION.
001500 SPECIAL-NAMES.
001600     CONDITION-CODE IS C-C.
001700 DATA DIVISION.
001800 WORKING-STORAGE SECTION.
001900 01  BEFORE-TIME         PIC 9(9) COMP.
002000 01  AFTER-TIME          PIC 9(9) COMP.
002100 01  DELTA-TIME          PIC 9(9) COMP.
002200 01  TOTAL-TIME          PIC 9(9) COMP.
002300 01  RUN-TIME            PIC 9(9) COMP.
002400 01 QUAL                     PIC X(16) VALUE "; ".
002500 01 MASTER-KEY               PIC X(16).
002600 01 DATA-BUFFER              PIC X(2000).
002700 01 MSG-BUFFER              PIC X(80).
002800 01 DBNAME                   PIC X(30) VALUE SPACES.
002900 01 M1                       PIC 9(4) COMP VALUE 1.
003000 01 M2                       PIC 9(4) COMP VALUE 2.
003100 01 M3                       PIC 9(4) COMP VALUE 3.
003200 01 M4                       PIC 9(4) COMP VALUE 4.
003300 01 M5                       PIC 9(4) COMP VALUE 5.
003400 01 M9                       PIC 9(4) COMP VALUE 9.
003500 01 M102                     PIC 9(4) COMP VALUE 102.
003600 01 M205                     PIC 9(4) COMP VALUE 205.
003700 01 M301                     PIC 9(4) COMP VALUE 301.
003800 01 M302                     PIC 9(4) COMP VALUE 302.
003900 01 DETAIL-LIST              PIC XX VALUE "@ ".
004000 01 DBDUMMY                  PIC 9(4) COMP VALUE 0.
004100 01 DBSTATUS.
004200    05 DBSTAT                PIC S9(4) COMP VALUE 0.
004300    05 LENGTH1               PIC 9(4) COMP VALUE 0.
004400    05 RECORD-NUMBER         PIC 9(9) COMP VALUE 0.
004500    05 CHAIN-COUNT           PIC 9(9) COMP VALUE 0.
004600    05 PREV-ENTRY            PIC 9(9) COMP VALUE 0.
004700    05 NEXT-ENTRY            PIC 9(9) COMP VALUE 0.
004800 PROCEDURE DIVISION.
004900 101-PROMPT-BASE.
005000     DISPLAY "BASE>" WITH NO ADVANCING.
005100     ACCEPT DBNAME (3:28) FREE.
005200     IF DBNAME (3:1) = " " THEN STOP RUN.
005300     CALL "DBOPEN" USING DBNAME, QUAL, M1, DBSTATUS.
005400     IF DBSTAT <> 0 THEN PERFORM 900-ERROR THRU 909-EXIT
005500        GO TO 101-PROMPT-BASE.
005600 105-PROMPT-SET.
005700     DISPLAY "DETAIL SET NAME>" WITH NO ADVANCING.
005800     ACCEPT QUAL FREE.
005900
006000 200-READ.
006100     CALL INTRINSIC "PROCTIME" GIVING BEFORE-TIME.
006200     CALL "DBGET" USING DBNAME, QUAL, M2,
006300          DBSTATUS, MASTER-KEY, DATA-BUFFER, DBDUMMY.
006400     IF DBSTAT <> 0 THEN PERFORM 910-FAULT.
006500     CALL INTRINSIC "PROCTIME" GIVING AFTER-TIME.
006600     SUBTRACT BEFORE-TIME FROM AFTER-TIME GIVING DELTA-TIME.
006700     ADD DELTA-TIME TO TOTAL-TIME.
006900     GO TO 200-READ.
007000
007100 900-ERROR.
007200     MOVE SPACES TO MSG-BUFFER.
007300     CALL "DBERROR" USING DBSTATUS, MSG-BUFFER, DBDUMMY.
007400     DISPLAY MSG-BUFFER.
007500 909-EXIT. EXIT.
007600 910-FAULT.
007700     PERFORM 900-ERROR THRU 909-EXIT.
007800     DISPLAY 'DBGET MSECS=    ' TOTAL-TIME.
007900     CALL INTRINSIC "PROCTIME" GIVING RUN-TIME.
008000     DISPLAY 'TOTAL CPU MSECS=' RUN-TIME.
008100     STOP RUN.
008200 919-EXIT. EXIT.
008300

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

ATOM RSS1 RSS2