Report XML MemberData Extensions

Visual FoxPro 9.0 provides extended metadata attributes for class members in the Class Designer using XML in a document format specified by the VFP MemberData Schema. While the Visual FoxPro Report System does not share the Class Designer, it shares the MemberData schema for similar extensibility purposes. Using MemberData extensions with reports, you can:

  • Specify custom design-time instructions for individual report layout elements, for use by through event hooks exposed by the Report and Label Designers.

  • Provide dynamic instructions for individual report layout elements that can be carried out by a ReportListener-derived object at run time.

This topic describes the MemberData schema components used for reporting, and provides examples using MemberData XML documents when you design and run reports.

Report XML MemberData Document Design

Report MemberData, like Class Design MemberData, contains a sequence of elements under a VFPData root node. For a complete listing of the shared MemberData schema (.xsd), see MemberData Extensibility. The following table describes the attributes specified for reporting use.

Note

The schema permits users to add attributes not explicitly specified. Any tools you create to parse or create the XML should allow for the possibility that additional, unknown attributes are present for one or more elements in the sequence. Tools should also handle the possibility that attributes not marked as required by the schema might be missing for one or more elements. The run-time example in this topic provides a model for this behavior.

The Style column of report and label definition files (.frx and .lbx tables) is reserved for storage of Report MemberData. For more information on the structure of reports and labels, see Understanding and Extending Report Structure.

You can use the default Report Builder Application to insert XML documents of the required structure into report and label records for individual layout elements. You can examine the results, to see Report XML MemberData example documents. For more information, see How to: Assign Structured Metadata to Report Controls.

Node name Node type Parent node Remarks and recommended usage

VFPData

Element

(required)

None

Root node for the MemberData document.

reportdata

Element

(required)

VFPData

An element containing metadata for a specific report or label definition table record.

name

Attribute

(required)

reportdata

Shared with Class Designer MemberData. Can be used, with the type attribute, to filter and manage reporting MemberData Records in a common global store, such as FoxCode.dbf. For more information, see _FOXCODE System Variable.

Note

Although this attribute is required, an empty value is permitted.

type

attribute

reportdata

Shared with Class Designer MemberData. Can be used, with the name attribute, to filter and manage records in a global store.

Note

When the default Report Builder Application creates Report MemberData, it places the value "R" in the type attribute, to distinguish these records from other types of MemberData.

script

attribute

reportdata

Shared with Class Designer MemberData, and specified, similarly to its use in class design, for use in reporting design-time extensions.

class

attribute

reportdata

Specified to hold the name of a class to be used for any and all of the following:

  • A template at design time, from which Report Builder extensions may apply attributes. Report Builder extensions which take this approach should document the attributes they transfer from the template class to the report or label element.

  • A helper class for designing the report or label element. Report Builder extensions taking this approach should specify a required interface for such classes and invoke the specified methods during design events. The helper class has access to the Report Builder's private data session and copy of the report or label table.

  • A helper class associated with the design-time script element. Report Builder extensions taking this approach can send the script to the helper class for processing, or they can run the script directly, sending a reference to the helper object as a parameter to the script.

  • A template class instantiated at run time by a ReportListener. The ReportListener can transfer attributes dynamically from the template class, documenting the set of attributes to be transferred. This approach allows all layout elements, in all reports, to share in changes you make to the template class, emulating class inheritance.

  • A helper class instantiated by a ReportListener to aid run-time processing of a specific report layout element and associated with run-time script processing.

classlib

attribute

reportdata

Specified to hold the name of the class library or procedure file (.vcx or .prg) from which the helper or template class will be instantiated. Reporting extensions should assume a file extension of vcx if none is included. Note that the class library or procedure file must be accessible to the extension. For a summary of how Visual FoxPro finds class definition, refer to the Remarks section of SET CLASSLIB Command.

declass

attribute

reportdata

Specified to hold the name of a DataEnvironment class in a visual class library (.vcx) to be used as a template for Cursor and Relation records in this report or label in the default Report Builder Application's implementation of the Load DataEnvironment event. The Report Builder Application also writes code binding an instance of this class to the report's run-time DataEnvironment events. For more information, see How to: Load Data Environments for Reports.

Note

The Report Builder Application uses the header record (first record) in the report or label definition table to store DataEnvironment class information, because this information is global to the report. It is good practice to follow this convention, storing global data in the first record's XML MemberData document. In the run-time example included in this topic, a run-time reporting extension opts to check this record for script appropriate to the BeforeReport and AfterReport events. These events are global in nature and not associated with any specific report or label layout element or record.

declasslib

attribute

reportdata

Specified to hold the filename of the visual class library or procedure file from which the DataEnvironment class should be instantiated, when the declass attribute holds the name of a DataEnvironment class, as described above. As an alternative, the default Report Builder Application offers users the ability to associate DataEnvironment records from another report or label (.frx or .lbx file) with the report. When users make this choice, the Report Builder Application stores the name of the report or label used as the DataEnvironment template in this attribute.

execute

attribute

reportdata

Specified for script used in run-time reporting extensions.

execwhen

attribute

reportdata

Specified for conditions to be evaluated by run-time reporting extensions to determine if, and when, the script contents of the execute attribute should run.

Tip

As shown in the example code in this topic, execwhen conditions can be evaluated flexibly; unlike the Print When conditions in a report they do not have to evaluate directly to a logical result.

Report XML MemberData at Design Time

As described in the table above, the Report Builder Application uses the declass and declasslib attributes of the Report XML MemberData stored in the header record of the report or label definition file. By default, it does not use any other MemberData you store in the report or label. However, you can easily leverage the Report Builder Application's extension architecture to read and use the XML.

The following class implements the Report Builder Application's exit handler mechanism. When registered with the Report Builder Application, this class receives information about the Report Designer event that occurred and whether the Report Builder Application made any changes to the current report layout element. If the layout element contains text, and if changes occurred, the handler object checks for a template class in the XML MemberData. If one exists, and if it has a property with the name Fontname, the handler asks the user whether the template class's font should be applied to the report layout element.

Note

For more information on registering custom handlers and filters in the Report Builder Application's registry table and implementing the required API, see Report Builder Event Handler Registry Table. Use of the exit handler mechanism is convenient, but illustrates only a fraction of the potential you have for design-time interactions using Report Designer event hooks and Report XML MemberData.

DEFINE CLASS TemplateObjectHandler AS Custom
* register this as an exit handler
PROCEDURE Execute( oEvent )
  IF BITTEST(oEvent.ReturnFlags,1) AND ;
    INLIST(FRX.ObjType,5,8) AND NOT EMPTY(FRX.STYLE)
    LOCAL lcAlias, loX
    lcAlias = "T"+SYS(2015)
    TRY  
      XMLTOCURSOR(FRX.Style,lcAlias)
      SELECT (lcAlias)
      IF NOT EMPTY(Class) AND ;
        MESSAGEBOX("(Re)apply Font from Template Object?",4) = 6
        IF EMPTY(ClassLib)
          loX = CREATEOBJECT(ALLTRIM(Class))
        ELSE
          loX = NEWOBJECT(ALLTRIM(Class),ALLTRIM(Classlib))
        ENDIF   
        IF VARTYPE(loX) = "O" AND ;
          PEMSTATUS(loX,"Fontname",5)
          REPLACE Fontface WITH loX.Fontname IN FRX
        ELSE
          MESSAGEBOX("Could not apply template.")    
        ENDIF
      ENDIF   
    CATCH WHEN .T.
      * not valid XML
      * or other error occurred
    FINALLY
      IF USED(lcAlias)
        USE IN (lcAlias)
      ENDIF
      SELECT FRX   
    ENDTRY
  ENDIF
  RETURN .T.
ENDPROC
ENDDEFINE

Report XML MemberData at Run Time

The following example leverages the run-time effects processing architecture suggested in Considerations for Creating New Report Output Types.

The superclass in the example, FXMemberData is a custom-derived class implementing the simple FX API, and suitable for being called from an instance of the FXListener class, as described in that topic. FXMemberData is an effect object with the ability to read and parse Report XML MemberData, placing the results in a cursor indexed on a column, FRXRecno, associating each record with the elements of the original report or label definition table.

FXMemberData performs its service at the beginning of the report run. For the rest of the report run, if the value of its ApplyMemberData member is set to True (.T.), FXMemberData positions the record pointer of its cursor appropriately for the current report event, but does not take any other action.

Having this type of object avoids the necessity of having each ReportListener or effect object requiring access to the structured metadata parse the XML document separately. With the metadata easily accessible to them in this common cursor, each object using the data can SELECT the columns of interest to it into a separate, private cursor, with additional columns for dynamic changes they might want to make at run time for their own purposes.

Note

To find the relevant cursor created by FXMemberData or a similar provider, other objects can investigate the FRXDataSession to find a cursor of the correct structure, parsing the XML themselves if they cannot find one. Alternatively, they can observe a simple convention, shown here as MemberDataAlias, of a ReportListener property holding the appropriate alias. Notice that FXMemberData uses the AddProperty Method to attach this property to any ReportListener.

A second class derived from FXMemberData, FXProcessMemberDataScript, shows you some strategies for using the Execute and ExecWhen attributes of Report XML MemberData. This class evaluates ExecWhen to determine when to invoke the script in Execute. If it determines that it should process the script, it checks to see if a PARAMETERS or LPARAMETERS line is the first line in the script. If not, it prepends a LPARAMETERS statement to the script, to allow it to pass all the parameters received by the ApplyFX method of the effect class API, which effectively allow effect objects to handle and adjust all report events' parameters. The LPARAMETERS statement it creates also includes a reference to the FX object as the first parameter, before all the parameters received in the ApplyFx method. Having made these adjustments, it uses the EXECSCRIPT( ) Function to process the script, passing these parameters to the script.

* to use this class, follow the pattern
* illustrated for use of the FXListener class,
* as follows :
LOCAL loPrimaryRL
* the following line assumes availability of
* the class definition for FXListener listed in 
* code example in the topic
* Considerations for Creating New Report Output Types:
loPrimaryRL = CREATEOBJECT("FXListener") 
* add successor ReportListeners if desired
loPrimaryRL.FXs.Add("FXProcessMemberDataScript")
* or use its superclass if you don't 
* need script processing but want to
* parse the XML MemberData:
* loPrimaryRL.FXs.Add("FXMemberData")
* add other effect objects to the collection
* as required

* Effect class suitable for calling
* by FXListener example class

* Because it works with unknown attributes
* and unknown memberdata requirements,
* FXMemberData requires that the values you use
* for all custom attributes be evaluated by 
* XMLTOCURSOR() as a string.  Values
* that do not evaluate as a string will error.
* This behavior makes it possible
* for you or other users to use multiple data types 
* for the same custom attributes on different FRX
* records.
* When you use a non-string value, you should 
* re-datatype it as appropriate for use in your code. 
* (Use EVAL() or otherwise translate the data
* type as needed.)

DEFINE CLASS FXMemberData AS Custom
   MemberDataAlias = ""
   ApplyMemberData = .F.
   PROCEDURE ApplyFX(toListener, tcProgram,;
                     tP1, tP2, tP3, tP4, tP5, tP6, ;
                     tP7, tP8, tP9, tP10, tP11, tP12)
      LOCAL liSession, liSelect, llInBeforeReport
      llInBeforeReport = (ATC("BeforeReport", tcProgram) > 0)
      IF (llInBeforeReport OR THIS.ApplyMemberData) AND ;
         (TYPE("toListener.FRXDataSession") = "N" AND ;
              toListener.FRXDataSession > -1)
         liSession = SET("DATASESSION")
         SET DATASESSION TO (toListener.FRXDataSession)
         liSelect = SELECT()
         IF llInBeforeReport
             * pull the memberdata out of the FRX for later use
             THIS.PullMemberData(toListener)
         ENDIF
         IF THIS.ApplyMemberData
            * this FX object
            * might apply the results of
            * the memberdata pull
            * or it might just make them
            * available to other FX objects
            * after the initial read
            SELECT (THIS.MemberDataAlias)
            THIS.UseMemberData(;
                 toListener, tcProgram,;
                 @tP1, @tP2, @tP3, @tP4, @tP5, @tP6, ;
                 @tP7, @tP8, @tP9, @tP10, @tP11, @tP12)
         ENDIF            
         SELECT (liSelect)
         SET DATASESSION TO (liSession)
      ENDIF                          
   ENDPROC
   PROTECTED PROCEDURE UseMemberData(toListener, tcProgram,;
                        tP1, tP2, tP3, tP4, tP5, tP6, ;
                        tP7, tP8, tP9, tP10, tP11, tP12)   
       LOCAL lnFRXRecno
       lnFRXRecno = -1
       DO CASE
       CASE ATC(".Before",tcProgram) > 0 OR ATC(".After",tcProgram) > 0
          DO CASE
          CASE RAT("REPORT",UPPER(tcProgram)) = (LEN(tcProgram)-5)
             lnFRXRecNo = 1
             * pull global data
          CASE VARTYPE(tP2) = "N" && Band events
             lnFRXRecNo = tP2          
          OTHERWISE
             * called inappropriately
          ENDCASE
       CASE VARTYPE(tP1) = "N"  && Render, other events
          lnFRXRecno = tP1   
       OTHERWISE
          * called inappropriately
       ENDCASE
       IF NOT SEEK(lnFRXRecno,THIS.MemberDataAlias,"FRXRecno")
          lnFRXRecno = -1
       ENDIF
       RETURN (lnFRXRecno # -1)
   ENDPROC
   PROTECTED PROCEDURE PullMemberData(toListener)
      LOCAL lcAlias, lcTempAlias, lcAttributes, liIndex, loAttr
      IF TYPE("toListener.MemberDataAlias") = "C" AND ;
         NOT EMPTY(toListener.MemberDataAlias)
         lcAlias = toListener.MemberDataAlias
      ELSE
         lcAlias = "M"+SYS(2015)
         toListener.AddProperty("MemberDataAlias", lcAlias)
         * "publish" this for others in case they want it
      ENDIF
      THIS.MemberDataAlias = lcAlias
      lcTempAlias = "T" + SYS(2015)
      CREATE CURSOR (lcAlias)  ;
                    (FRXRecno I, Name M, Type M, ;
                     ExecWhen M, Execute M, Class M, ;
                     ClassLib M, DEClass M, DEClassLib M)
      * we're going to take every attribute, whether 
      * we understand the column or not, 
      * but we'll start off with the 
      * core set minus script since script attribute is 
      * officially reserved for design-time use
      lcAttributes = ;
          "|FRXRecno|ExecWhen|Execute|Class|" + ;
          "Classlib|Name|Type|DEClass|DEClassLib|"
      SELECT FRX
      SCAN FOR NOT EMPTY(Style)
          TRY 
             XMLTOCURSOR(Style,lcTempAlias)
          CATCH WHEN .T.
             * not valid XML
          FINALLY
             IF USED(lcTempAlias) 
                IF RECCOUNT(lcTempAlias) > 0 
                   SELECT (lcTempAlias)
                   FOR liIndex = 1 TO FCOUNT()
                       IF ATC("|"+FIELD(liIndex)+"|",lcAttributes) = 0
                          ALTER TABLE (lcAlias) ;
                           ADD COLUMN (FIELD(liIndex)) M
                          lcAttributes = lcAttributes + ;
                           FIELD(liIndex) + "|"
                       ENDIF
                   ENDFOR
                   SCATTER MEMO NAME loAttr
                   INSERT INTO (lcAlias) FROM NAME loAttr
                   REPLACE FRXRecno WITH RECNO("FRX") IN (lcAlias)
                ENDIF
                USE IN (lcTempAlias)
             ENDIF
          ENDTRY
          loAttr = NULL
       ENDSCAN
       SELECT (lcAlias)
       INDEX ON FRXRecno TAG FRXRecno
   ENDPROC
ENDDEFINE

DEFINE CLASS FXProcessMemberDataScript AS FXMemberData
   ApplyMemberData = .T.
   PROTECTED PROCEDURE UseMemberData(toListener, tcProgram,;
                        tP1, tP2, tP3, tP4, tP5, tP6, ;
                        tP7, tP8, tP9, tP10, tP11, tP12)   
       IF DODEFAULT(toListener, tcProgram,;
                    @tP1, @tP2, @tP3, @tP4, @tP5, @tP6, ;
                    @tP7, @tP8, @tP9, @tP10, @tP11, @tP12)
                    
          * We are now positioned on the correct
          * record by the parent class,
          * and can take action based on the memberdata contents.
          * For example, if we're in BeforeReport,
          * we could instantiate a collection of the appropriate
          * template objects for each label or text record that has a 
          * class and classlib available.
          * For each EvaluateContents or Render
          * event we can call methods of the class or
          * apply font attributes to the runtime result.
          LOCAL loMemberdata, llExecute 
          SCATTER MEMO NAME loMemberdata
          IF NOT EMPTY(loMemberdata.Execute)
             IF EMPTY(loMemberdata.ExecWhen)
                llExecute = .T.
             ELSE
                DO CASE
                CASE ATC(loMemberData.ExecWhen,tcProgram) > 0
                   * simple event evaluation
                   * ExecWhen contains an event name
                   * Note that each event, via script,
                   * could potentially change the contents of
                   * ExecWhen to hold another value (the next
                   * event during which this script 
                   * should be evaluated)
                   llExecute = .T.
                CASE (TYPE(loMemberdata.ExecWhen) = "L") AND ;
                   EVALUATE(loMemberdata.ExecWhen)
                   * ExecWhen contains a logical expression 
                   * to be evaluated
                   llExecute = .T.
                CASE ATC(SUBSTR(tcProgram,RAT(".",tcProgram) + 1),;
                         loMemberData.ExecWhen) > 0
                   * ExecWhen contains a delimited string of events
                   llExecute = .T.
                ENDCASE
             ENDIF
             IF llExecute
                IF NOT (BETWEEN(ATC("PARAM", ;
                        ALLTRIM(CHRTRAN(loMemberData.Execute,;
                        CHR(10)+CHR(13), ;
                        SPACE(2)))),1,2))
                   * add a parameters statement; this adjustment
                   * should just happen the first time 
                   * any FRX record is processed.
                   loMemberData.Execute = ;
                   "LPARAMETERS toFX, toListener, tcProgram,;"+ ;
                    CHR(13) + CHR(10) + ;
                   "tP1, tP2, tP3, tP4, tP5, tP6,"+;
                   "tP7, tP8, tP9, tP10, tP11, tP12" + ;
                    CHR(13) + CHR(10) + ;
                   loMemberData.Execute
                   REPLACE Execute WITH loMemberData.Execute 
                ENDIF
                ExecScript(loMemberData.Execute,;
                    THIS, toListener, tcProgram,;
                    @tP1, @tP2, @tP3, @tP4, @tP5, @tP6, ;
                    @tP7, @tP8, @tP9, @tP10, @tP11, @tP12)
             ENDIF   
          ENDIF
       ENDIF                 
   ENDPROC                      
   
ENDDEFINE

To use a script-processing effect of this nature, you could add the following XML MemberData document to a Field or Expression control in the report layout holding a numeric value. This example provides automatic color changes for numeric values below 0, using the EvaluateContents event, and formats the negative numbers with parentheses, using the Render method.

Tip

Notice that the ExecWhen attribute indicates the script should be processed at these two points by specifying a delimited string ("|EvaluateContents|Render|"). This is one of several alternative means of evaluating ExecWhen provided by the FXProcessMemberDataScript class.

<VFPData>
<reportdata name="" type="R" script="" 
execwhen="|EvaluateContents|Render|"
execute=
"DO CASE 
 CASE ATC(&quot;Render&quot;,tcProgram) &gt; 0
  * Render's 7th parameter is
  * cContentstoBeRendered
  * notice the conversion from Unicode to DBCS
  tP7 = VAL(STRCONV(tp7,6))
  IF tp7 &lt; 0
     tP7 =  &quot;(&quot;+TRANS(ABS(tp7)) + &quot;)&quot;
  ELSE
     tP7 = TRANS(tP7)
  ENDIF
  * convert back to Unicode for use by the native ReportListener:
  tP7 = STRCONV(tp7,5)
OTHERWISE
  * EvaluateContents' second parameter
  * is objProperties
   IF VARTYPE(tP2.value) = "N" AND ;
      tP2.value &lt; 0
      tP2.penred = 255
      tP2.penblue = 0
      tP2.pengreen = 0
      tP2.reload = .T.
   ENDIF
ENDCASE"
class="" classlib="" declass="" declasslib=""/>
</VFPData>

Tip

The well-formed XML document above shows a number of escaped character references within the script; for example, a character such as < must be stored as the entity reference &lt; when it is part of the value of an attribute or element node in XML. When you create the script using the Report Builder Application's Run-time Extensions text box interface, you can type these characters as you normally do, without using the entity references. The Report Builder Application stores the document properly, escaping the characters as necessary, when you save the XML.

The following class is another class definition following the FX API. Unlike FXMemberData and its derived classes, FXMemberDataAware does not understand XML and does not read the MemberData directly. Instead, it reads the cursor produced by FXMemberData and understands its structure. If it finds the cursor in its environment, it uses the cursor, adding columns if desired. If the cursor is not available, it provides a temporary instance of FXMemberData during the BeforeReport method, so this temporary object can create the cursor.

FXMemberDataAware is an abstract class, performing no service during the report run. However, you can derive many FX classes from FXMemberDataAware, each with a specialized purpose. If you add instances of each FX to an FXListener's collection, they all share the same MemberData cursor during the report run. They can also create private MemberData extension cursors related to the shared cursor, as needed.

DEFINE CLASS FXMemberDataAware AS Custom

   MemberDataAlias = ""
   HasMemberData = .F.
     
   PROCEDURE ApplyFX(toListener, tcProgram,;
                     tP1, tP2, tP3, tP4, tP5, tP6, ;
                     tP7, tP8, tP9, tP10, tP11, tP12)
                 
      IF ATC("BeforeReport",tcProgram) > 0             
         THIS.VerifyMemberData(toListener)            
      ENDIF

      IF ATC("AfterReport",tcProgram) > 0
         THIS.DetachMemberData(toListener, .T.)
      ENDIF
         
    ENDPROC

   PROCEDURE VerifyMemberData(toListener)
      IF toListener.FRXDataSession = -1
         RETURN .F.
      ENDIF
      LOCAL loMemberData, liSelect, liSession
      liSession = SET("DATASESSION")
      SET DATASESSION TO (toListener.FRXDataSession)
      liSelect = SELECT()
      IF (EMPTY(THIS.MemberDataAlias) OR ;
         (NOT USED(THIS.MemberDataAlias)))
         * can be supplied by the Listener
         * by leveraging a different FX object,
         * but might not be, so in this case
         * let's scarf it up with a temporary object
         IF (NOT PEMSTATUS(toListener,"MemberDataAlias",5)) OR ;
            EMPTY(toListener.MemberDataAlias)
            THIS.MemberDataAlias = "M" + SYS(2015)
            toListener.AddProperty("MemberDataAlias", ;
                        THIS.MemberDataAlias)
         ELSE
            THIS.MemberDataAlias = toListener.MemberDataAlias
         ENDIF   
         IF NOT USED(THIS.MemberDataAlias)
            * could be sharing 
            loMemberData = NEWOBJECT("FXMemberData")
            loMemberData.MemberDataAlias = THIS.MemberDataAlias
            loMemberData.ApplyMemberData = .F.
            loMemberData.ApplyFX(toListener, "BeforeReport")
            SET DATASESSION TO (toListener.FRXDataSession) 
            IF USED(THIS.MemberDataAlias)
               * we can proceed...
               THIS.AlterMemberDataInfo()
            ENDIF
          ENDIF
       ENDIF          
       THIS.HasMemberData = USED(THIS.MemberDataAlias)         
       SELECT (liSelect)
       loMemberData = NULL       
       SET DATASESSION TO (liSession)    
       RETURN THIS.HasMemberData
    ENDPROC
    
    PROTECTED PROCEDURE AlterMemberDataInfo()
      * Hook for derived classes
      * to add their own columns,
      * or even to create private cursors
      * in the FRX Data session that
      * function in relation to the MemberData 
      * shared cursor.
    ENDPROC
      
    PROCEDURE DetachMemberData(toListener, tlCloseMemberDataTable)
       IF tlCloseMemberDataTable AND toListener.FRXDataSession > -1
          LOCAL liSession
          liSession = SET("DATASESSION")
          SET DATASESSION TO (toListener.FRXDataSession)
          IF USED(THIS.MemberDataAlias)
             USE IN (THIS.MemberDataAlias)
             IF PEMSTATUS(toListener,"MemberDataAlias",5)
                toListener.MemberDataAlias = ""
             ENDIF
          ENDIF
          SET DATASESSION TO (liSession)
       ENDIF    
       THIS.MemberDataAlias = ""
       THIS.HasMemberData = .F.
       
    ENDPROC
       
ENDDEFINE

See Also

Reference

ReportListener Object
BeforeReport Event
AfterReport Event
Render Method
EvaluateContents Event

Other Resources

Extending Reports at Design Time
Extending Reports at Run Time