ZenWorkspace.OnObjectCreated



OnObjectCreated(obObject As Dispatch)

Parameters

obObject As Dispatch
Object, the type depends to the created object (Variable,Picture,...)
ED
avaliable
RT
not used

Remarks

This event is fired when a new object is created.
A new object could be:


	- Template

	- Picture

	- Variable

	- Element

	- ......


Private Sub ZenWorkspace_OnObjectCreated(ByVal obObject As Object)
'this Event is fired, when a new object is created within a project...
Dim strObjectType As String
Dim obTemplate As Template
Dim obPicture As DynPicture
Dim obFunction As RtFunction
Dim obElement As Element
Dim obUser As User
Dim obRema As Rema
Dim obScript As Script
Dim obEdLimit As EdLimit
Dim obRGMRecipe As RGMRecipe
Dim obRecipe As Recipe
Dim obVarAssignment As VarAssignment
Dim obVariable As Variable
Dim obTimeFunction As TimeFunction
Dim ErrH As Label
On Error GoTo ErrH
	'depending to the type of the created object, different actions can be done...
	strObjectType = TypeName(obObject)
	Select Case strObjectType
		Case "ITemplate"
			Set obTemplate = obObject
			Debug.Print "Template created......> " & obTemplate.Name
			Debug.Print "----- in Project......> " & obTemplate.Parent.Parent.Name
		Case "IDynPicture"
			Set obPicture = obObject
			Debug.Print "Picture created.......> " & obPicture.Name
			Debug.Print "---- in Project.......> " & obPicture.Parent.Parent.Name
		Case "IRtFunction"
			Set obFunction = obObject
			Debug.Print "Function created......> " & obFunction.Name
			Debug.Print "----- in Project......> " & obFunction.Parent.Parent.Name
		Case "IElement"
			Set obElement = obObject
			Debug.Print "Element created.......> " & obElement.Name
			Debug.Print "---- in Picture.......> " & obElement.Parent.Parent.Name
			Debug.Print "---- in Project.......> " & obElement.Parent.Parent.Parent.Parent.Name
		Case "IScript"
			Set obScript = obObject
			Debug.Print "Script created........> " & obScript.Name
			Debug.Print "--- in Project........> " & obScript.Parent.Parent.Name
		Case "IRema"
			Set obRema = obObject
			Debug.Print "REMA created..........> " & obRema.Name
			Debug.Print "- in Project..........> " & obRema.Parent.Parent.Name
		Case "IUser"
			Set obUser = obObject
			Debug.Print "User created..........> " & obUser.Name
			Debug.Print "- in Project..........> " & obUser.Parent.Parent.Name
		Case "IEdLimit"
			Set obEdLimit = obObject
			Debug.Print "Limit created.........> "
			Debug.Print "---- Variable.........> " & obEdLimit.Parent.Name
			Debug.Print "-- in Project.........> " & obEdLimit.Parent.Parent.Parent.Name
		Case "IRGMRecipe"
			Set obRGMRecipe = obObject
			Debug.Print "RMG Recipe created....> " & obRGMRecipe.DynProperties("RecipeName")
			Debug.Print "----- in RGM Group....> " & obRGMRecipe.Parent.DynProperties("Name")
			Debug.Print "------- in Project....> " & obRGMRecipe.Parent.Parent.Parent.Name
		Case "IRecipe"
			Set obRecipe = obObject
			Debug.Print "Recipe created........> " & obRecipe.Name
			Debug.Print "--- in Project........> " & obRecipe.Parent.Parent.Name
		Case "ITimeFunction"
			Set obTimeFunction = obObject
			Debug.Print "TimeFunction created..> " & obTimeFunction.Name
			Debug.Print "--------- in Project..> " & obTimeFunction.Parent.Parent.Name
		Case "IVarAssignment"
			Set obVarAssignment = obObject
			Debug.Print "VarAssignment created.> " & obVarAssignment.Name
			Debug.Print "---------- in Project.> " & obVarAssignment.Parent.Parent.Name
		Case "IVariable"
			Set obVariable = obObject
			Debug.Print "Variable created......> " & obVariable.Name
			Debug.Print "----- in Project......> " & obVariable.Parent.Parent.Name
		Case Else
			Debug.Print strObjectType
	End Select
	Exit Sub
ErrH:
	Debug.Print "[ERROR] " & Err.Number & " - " & Err.Description
	Resume Next
End Sub


See Also

ZenWorkspace, Dispatch