tips:revmedia:v2i3a4

VROOM - Window Processing II

Published ByDateVersionKnowledge LevelKeywords
Sprezzatura Ltd01 JUL 19901.15+EXPERTWINDOW, PROCESSING, OCONV, SYMBOLIC, RLIST, VROOM

The last issue dealt with the way in which window flow can impair performance, specifically in relation to OCONVs and symbolics. Example code to deal with this problem by removing the OCONVs and symbolics at pre save and restoring them pre read is presented below. Note that the best performance improvements will be seen where the OCONVs and symbolics make reference to other files, eg code table lookups. To use the program, enter compile and catalog it and then put commuter calls to it on the PRE.INIT, PRE.READ and PRE.SAVE hooks. (EG Pre Save Code = S Pre Save Command = STRIPPER,PRE.SAVE. The code listing that follows is longer than our preferred length but this in view of the numerous comments contained therein it is felt to be acceptable.

STRIPPER
  SUBROUTINE STRIPPER(BRANCH)
  *
  * Author AMcA with acknowledgements to Stefan Gilboy of ICS (Sales) for
  *        the original idea
  * Date   April 1990
  *
    BEGIN CASE
       CASE BRANCH = "PRE.INIT" ; GOSUB PRE.INIT
       CASE BRANCH = "PRE.READ" ; GOSUB PRE.READ
       CASE BRANCH = "PRE.SAVE" ; GOSUB PRE.SAVE
    END CASE
  RETURN

  PRE.INIT:
    *
    * It is necessary to make a copy of all of the symbolics and OCONVs so
    * that they can be restored later when they have been removed. Anywhere
    * can be used, this example uses REGISTER(2). Note that as this logic
    * takes place at PRE.INIT the template structure is still in @RECORD so
    * this is manipulated
    *
    CTR = @RECORD<1> + 1
    NEW_REG = ""
    FOR X = 2 TO CTR
       *
       * Note that we store the field name and OCONV for EVERY prompt
       * regardless of the relevance of same. It is a moot point whether the
       * extra checks required to implement the extra logic might slow the
       * program down sufficiently to nullify the benefits accrued therefrom
       *
       NEW_REG<X-1> = @RECORD<X,2> : @VM : @RECORD<X,13>
       *
       * Don't null down key prompts as this seems to cause problems under
       * some circumstances. For all other fields though remove the field
       * name if symbolic to prevent recalculation and the OCONV
       *
       IF X > 2 THEN
          IF @RECORD<X,3> = "S" THEN @RECORD<X,2> = ""
          @RECORD<X,13> = ""
       END
    NEXT
    *
    * Now store NEW_REG in REGISTER(2)
    *
    @RECORD = FIELDSTORE(@RECORD,"รท",37,1,NEW_REG)
  RETURN

  AREV.COMMON:
    *
    * Note - cannot be done at top of program as it is not loaded until
    * after PRE.INIT
    *
    $INSERT AREV.COMMON
  RETURN

  PRE.READ:
    GOSUB AREV.COMMON
    *
    * If @ID is null then this is the "Dummy" pre read highlighted in the
    * last issue. Under these circumstances it makes no sense to reload the
    * missing information
    *
    IF @ID # "" THEN
       FOR X = 1 TO W.CNT
          W(X)<2> = REGISTER(2)<X,1>
          W(X)<13> = REGISTER(2)<X,2>
       NEXT
    END
  RETURN

  PRE.SAVE:
    GOSUB AREV.COMMON
    *
    * Remove information
    *
    FOR X = 1 TO W.CNT
       IF W(X)<3> = "S" THEN W(X)<2> = ""
       W(X)<13> = ""
    NEXT
  RETURN

As evidenced in the last issue, OCONVs are called an inordinate amount of times in entry windows. If user-defined OCONVs which produce disk i/o are being used then performance will degrade dramatically. It is therefore only practical to examine ways of decreasing this overhead.

One simple but effective improvement that can easily be made is to examine the value that the program is being asked to OCONV and then compare it with the value last OCONVed. If the two values are the same then there is no point in recalculating the value - simply use the result produced last time. The decision of where to store this information is a purely personal one but the higher fields in @RECORD are convenient if you remember to null them down on a Pre Save.

The following logic serves to illustrate this. It assumes the basic structure of the user defined conversion has been defined and the data to convert is in PASSED_DATA whilst the data to return is in RETURNED_DATA.

     * Normal OCONV code precedes
     IF PASSED_DATA = @RECORD<100,1> THEN
        RETURNED_DATA = @RECORD<100,2>
     END ELSE
        @RECORD<100,1> = PASSED_DATA
        GOSUB CALCULATE_CONV
        @RECORD<100,2> = RETURNED_DATA
     END

Note that in the example given above the passed data is stored in value one of the field and the OCONVed result is stored in field 2. This will obviously not work if the field being OCONVed is MVed.

It is frequently the case that symbolics make reference to other symbolics. As these need to be recalculated every time they are referenced this can reduce list performance. Extrapolating upon the technique used above we could modify our symbolics so that those symbolics that others used could place their result both in @ANS and @RECORD<x>. The other symbolics could reference this field and if null calculate the appropriate value and insert it. This means that in any list statement the same symbolic would only ever be calculated once regardless of how many times it was referenced. This sort of approach is simple to implement - the only problem is remembering to modify new symbolics in line with pre-existing ones.

The performance improvements gained can be significant, in one disk intensive operation at a client recently, list speed was improved by an order of magnitude by applying this technique. The following code illustrates the technique - using two dictionary items, HOURS_TO_DATE and AMOUNT_TO_DATE (assume CALCULATE_HTD and CALCULATE_ATD exist and return the relevant information).

  * Hours to date, stored temporarily in @RECORD<100>
  IF @RECORD<100> THEN
     @ANS = @RECORD<100>
  END ELSE
     GOSUB CALCULATE_HTD
     @ANS = HTD
     @RECORD<100> = HTD
  END

  * Amount to date, stored temporarily in @RECORD<101>
  IF @RECORD<101> THEN
     @ANS = @RECORD<101>
  END ELSE
     IF @RECORD<100> THEN
        HTD = @RECORD<100>
     END ELSE
        HTD = {HOURS_TO_DATE}
        @RECORD<100> = HTD
     END
     GOSUB
     CALCULATE_ATD
     @ANS = ATD
     @RECORD<101> = ATD
  END

(Volume 2, Issue 3, Pages 4-6)

  • tips/revmedia/v2i3a4.txt
  • Last modified: 2024/06/19 20:20
  • by 127.0.0.1