ibmi-brunch-learn

Announcement

Collapse
No announcement yet.

DB File Trigger(s)

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • DB File Trigger(s)

    Anyone out there know much about DB Tiggers?? I am a little familar with them and I have a task to save the New Record Image on an *Insert event. What I am having trouble with is the "Old Record Null Map" field. Specifically how to calulate the length of this field. I know I have to adjust the Old-Record and New-Record field's record lengths to coinside with the physical file length the trigger is on and the Null Map is the map of the null record fields of the DB file. The book says this charater sting has a length the same as the number of fields in the file. Well not true see Example. Or is it the number of nulls found in these five field??

    PHP Code:
      LINKAGE SECTION.                                     
         
    01  LK-PARM1.                                        
             
    03 FILE-NAME             PIC X(10).              
             
    03 LIB-NAME              PIC X(10).              
             
    03 MEM-NAME              PIC X(10).              
             
    03 TRG-EVENT             PIC X(01).              
             
    03 TRG-TIME              PIC X(01).              
             
    03 CMT-LCK-LVL           PIC X(01).              
             
    03 FILLER                PIC X(03).              
             
    03 DATA-AREA             PIC 9(08BINARY.       
             
    03 RR-NUMBER             PIC 9(08BINARY.       
             
    03 FILLER                PIC X(04).              
             
    03 DATA-OFFSET.                                  
                   
    05 OLD-REC-OFF     PIC 9(08BINARY.       
                   
    05 OLD-REC-LEN     PIC 9(08BINARY.       
                   
    05 OLD-REC-NMAP    PIC 9(08BINARY.       
                   
    05 OLD-REC-NLEN    PIC 9(08BINARY.       
                   
    05 NEW-REC-OFF     PIC 9(08BINARY.       
                   
    05 NEW-REC-LEN     PIC 9(08BINARY.       
                   
    05 NEW-REC-NMAP    PIC 9(08BINARY.
                   
    05 NEW-REC-NLEN    PIC 9(08BINARY.                  
                   
    05 FILLER          PIC X(16).                         
             
    03 RECORD-INFO.                                             
       * 
    Old and New Image(sare the R/L of the file/data being saved  
                   05 OLD
    -IMAGE       PIC X(37).                         
                   
    05 OLD-NULL-MAP    PIC X(18).                         
                   
    05 NEW-IMAGE       PIC X(37).                         
                   
    05 NEW-NILL-MAP    PIC X(09). 
    The DB file is 37 positions long and has five fields. I had to use 18 on OLD-NULL-MAP because when I was debugging it I saw that's how many positions were between OLD-IMAGE and NEW-Image.

    How do I calculate the length of this so my positioning is not off for New-Record-Image??

  • #2
    Re: DB File Trigger(s)

    Does it have to be in cobol ??

    RPG look here http://www.code400.com/forum/showthr...hlight=trigger


    jamie
    All my answers were extracted from the "Big Dummy's Guide to the As400"
    and I take no responsibility for any of them.

    www.code400.com

    Comment


    • #3
      Re: DB File Trigger(s)

      I can do it in ether language but the thing is you are calculating the position and sub stringing it out of the buffer area. The book doesn't go into very much detail about this calculation, not at all. So I have some amo to go foward, thank you!

      -Dan

      Comment


      • #4
        Re: DB File Trigger(s)

        Hi there; you can not even both with using a program and just use sql.

        Look at the end of the thread for the complete solution.

        http://www.code400.com/forum/showthr...ht=sql+trigger

        Hunting down the future ms. Ex DeadManWalks. *certain restrictions apply

        Comment


        • #5
          Re: DB File Trigger(s)

          Here's a template that works with any file. Just change the file name to the file you are using. It uses pointers and soft codes the positions, so as the buffer changes, the program handles it. It a slightly modified version of the sample in the IBM book.

          PHP Code:

               F
          PROGRAM DESC Process triggers template                         *
               
          F********************************************************************
               
          F
               D
               D  NulTypePtr     S               
          *
               
          D  TypeBin4       S              9B 0 Based(NulTypePtr)
               
          D  TypeChr        S              1A   Based(NulTypePtr)
               
          D  TypeSysNam     S             10A   Based(NulTypePtr)
               
          D  TypePtr        S               *   Based(NulTypePtr)
               
          D
               D  TgBufLen       S                   Like
          (TypeBin4)
               
          D  TgBfrPtr       S                   Like(TypePtr)
               
          D  TgAftPtr       S                   Like(TypePtr)
               
          D  TgBufSiz       C                   Const(%size(TgBufChr))
               
          D
               D TgBufDS         DS
               D  TgFile                             Like
          (TypeSysNam)
               
          D  TgLib                              Like(TypeSysNam)
               
          D  TgMbr                              Like(TypeSysNam)
               
          D  TgTrgEvt                           Like(TypeChr)
               
          D  TgTrgTime                          Like(TypeChr)
               
          D  TgCmtLvl                           Like(TypeChr)
               
          D  TgReserve1                    3A
               D  TgCcsId                            Like
          (TypeBin4)
               
          D  TgReserve2                    8A
               D  TgBfrOfs                           Like
          (TypeBin4)
               
          D  TgBfrLen                           Like(TypeBin4)
               
          D  TgBfrNulOf                         Like(TypeBin4)
               
          D  TgBfrNulLn                         Like(TypeBin4)
               
          D  TgAftOfs                           Like(TypeBin4)
               
          D  TgAftLen                           Like(TypeBin4)
               
          D  TgAftNulOf                         Like(TypeBin4)
               
          D  TgAftNulLn                         Like(TypeBin4)
               
          D  TgBufChr               1  32767A
               D   TgBufAry                     1A   Overlay
          (TgBufChr)
               
          D                                       DIM (%size(TgBufChr))
               
          D
               D SDS            SDS
               D  WSID                 244    253
               D  USRID                254    263
               D  PGMID            
          *PROC
               D
               D
               D
          ***********************************************************************
               
          D**>>> On the next two definitionsput the based-on file name    <<<
               
          D**>>>   in the ExtName parameter                                 <<<
               
          D***********************************************************************
               
          D  BfFile       E DS                  ExtName(MBALREP)                     <- TRIGGER FILE
               D                                       Prefix
          (Bf_)
               
          D                                       Based(TgBfrPtr)
               
          D
               D  AfFile       E DS                  ExtName
          (MBALREP)                     <- TRIGGER FILE
               D                                       Prefix
          (Af_)
               
          D                                       Based(TgAftPtr)
               
          D*****
               
          D
               D
               C     
          *Entry        PList
               C     TgBufDs       Parm                    TgBufDs
               C     TgBufLen      Parm                    TgBufLen
               C
               C                   
          Eval      TgBfrPtr = %addr(TgBufAry(TgBfrOfs+1))
               
          C                   Eval      TgAftPtr = %addr(TgBufAry(TgAftOfs+1))
               
          C
               C
          *****
               
          C*
               
          C*  The based-on-file fields are now prefixed with Bf_  for before values
               C
          *                       and are now prefixed with Af_  for after  values
               C
          *
               
          C*****
               
          C
               C
          *  Call insert subroutines
               C                   
          IF        (TgTrgEvt '1')                             INSERT
               C                   
          IF        (TgTrgTime '1')                              AFTER
               C                   EXSR      AfterInsert
               C                   
          ENDIF
               
          C                   IF        (TgTrgTime '2')                              BEFORE
               C                   EXSR      BeforeInsert
               C                   
          ENDIF
               
          C                   ENDIF
               
          C
               C
          *  Call delete subroutines
               C                   
          IF        (TgTrgEvt '2')                             DELETE
               C                   
          IF        (TgTrgTime '1')                              AFTER
               C                   EXSR      AfterDelete
               C                   
          ENDIF
               
          C                   IF        (TgTrgTime '2')                              BEFORE
               C                   EXSR      BeforeDelete
               C                   
          ENDIF
               
          C                   ENDIF
               
          C
               C
          *  Call update subroutines
               C                   
          IF        (TgTrgEvt '3')                             UPDATE
               C                   
          IF        (TgTrgTime '1')                              AFTER
               C                   EXSR      AfterUpdate
               C                   
          ENDIF
               
          C                   IF        (TgTrgTime '2')                              BEFORE
               C                   EXSR      BeforeUpdate
               C                   
          ENDIF
               
          C                   ENDIF
               
          C
               C                   
          Eval      *INLR = *on
               C
               C
               C
          ********************************************************************
               
          CAfter Insert Processing                                          *
               
          C********************************************************************
               
          C     AfterInsert   BEGSR
               C
               C                   ENDSR
               C
               C
               C
          ********************************************************************
               
          CBefore Insert Processing                                         *
               
          C********************************************************************
               
          C     BeforeInsert  BEGSR
               C
               C                   ENDSR
               C
               C
               C
               C
          ********************************************************************
               
          CAfter Delete Processing                                          *
               
          C********************************************************************
               
          C     AfterDelete   BEGSR
               C
               C                   ENDSR
               C
               C
               C
          ********************************************************************
               
          CBefore Delete Processing                                         *
               
          C********************************************************************
               
          C     BeforeDelete  BEGSR
               C
               C                   ENDSR
               C
               C
               C
          ********************************************************************
               
          CAfter Update Processing                                          *
               
          C********************************************************************
               
          C     AfterUpdate   BEGSR
               C
               C                   ENDSR
               C
               C
               C
          ********************************************************************
               
          CBefore Update Processing                                         *
               
          C********************************************************************
               
          C     BeforeUpdate  BEGSR
               C
               C                   ENDSR 

          Comment

          Working...
          X