Callback - loadImage
Enables you to create a single procedure that loads all the images required for the Ribbon.
In the root node of your customisation there is a callback attribute called loadImage
This is used in conjunction with the 'image' attribute on individual controls.
The callback attribute 'loadImage' is called everytime the Ribbon asks for an image.
This allows you to define one image handler for the entire application.
<customUI xmlns="??"
loadImage="OnLoadImage"/>
<gallery id="??">
<item id="??" image="MyImage.jpg"/>
Public Sub OnLoadImage(ByVal sImageName As String, _
ByRef Image As Variant)
SetImage = LoadPicture("C:\Temp\" & sImageName)
End Sub
The <customUI> element's loadImage attribute enables you to specify a callback that can load all images. After you set up this callback procedure, Office calls the callback procedure and passes the string from the image attribute for each control that loads images.
You do not need to implement the getImage callback multiple times, such as one time for each control that requires images.
<customUI xmlns="http://schemas.microsoft.com/office/2006/01/customui"
loadImage="GetImage">
<button id="myButton" image="mypic.jpg" />
To supply the button's image, Office calls the GetImage function.
It passes the parameter "mypic.jpg" and expects an IPictureDisp object in return.
By using this technique, you can write a single callback procedure that returns all the images your customization needs, without having to write each individual control's getImage callback.
Note that the loadImage callback is not called again when you call the Ribbon's Invalidate method or InvalidateControl method.
For the controls that need to change images dynamically at run time, use the getImage callback.
For example, you could use the code from the following example to provide your customization's images.
The getImage callback method must return a stdole.IPictureDisp type, so you usually need to convert your images to this type.
To perform these conversions, you can use the following PictureConverter class, which inherits from the AxHost class.
Add a DoEvents statement immediately after invalidating the ribbon
Public Sub InitialiseAddInsRibbon(ribbon As IRibbonUI)
set mRibbonUI = ribbon
End Sub
Public Sub RefreshAddInsRibbon
mRibbonUI.Invalidate
DoEvents
End Sub
Use a single procedure for similar callbacks
Button_getVisible - handles all visibility callbacks then use a select-case
Always refer to a controls ID, never the Tag
2007 - you can change the visibility of a separator at runtime
custom icon sizes (32/16) generates blank error messages
Sub GetImage(Control As IRibbonControl, ByRef image)
Select Case Control.ID
Case "gallery1"
image = "ContentControlBuildingBlockGallery"
Case "gallery2"
Set image = LoadImage("CustomeImage" )
Case Else
'Do Nothing
End Select
End Sub
Private Type GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(0 To 7) As Byte
End Type
Private Type PICTDESC
Size As Long
Type As Long
hPic As Long
hPal As Long
End Type
Private Type GdiplusStartupInput
GdiplusVersion As Long
DebugEventCallback As Long
SuppressBackgroundThread As Long
SuppressExternalCodecs As Long
End Type
Private Declare Function GdiplusStartup Lib "GDIPlus" (token As Long, _
inputbuf As GdiplusStartupInput, Optional ByVal outputbuf As Long = 0)
As Long
Private Declare Function GdipCreateBitmapFromFile Lib "GDIPlus" ( _
ByVal filename As Long, bitmap As Long) As Long
Private Declare Function GdipCreateHBITMAPFromBitmap Lib "GDIPlus" ( _
ByVal bitmap As Long, _
hbmReturn As Long, _
ByVal background As Long) As Long
Private Declare Function GdipDisposeImage Lib "GDIPlus" ( _
ByVal image As Long) As Long
Private Declare Function GdiplusShutdown Lib "GDIPlus" ( _
ByVal token As Long) As Long
Private Declare Function OleCreatePictureIndirect Lib "olepro32.dll" ( _
PicDesc As PICTDESC, _
RefIID As GUID, _
ByVal fPictureOwnsHandle As Long, _
IPic As IPicture) As Long
Public Function LoadImage(ByVal strFName As String) As IPicture
Dim uGdiInput As GdiplusStartupInput
Dim hGdiPlus As Long
Dim hGdiImage As Long
Dim hBitmap As Long
uGdiInput.GdiplusVersion = 1
If GdiplusStartup(hGdiPlus, uGdiInput) = 0 Then
If GdipCreateBitmapFromFile(StrPtr(strFName), hGdiImage) = 0 Then
GdipCreateHBITMAPFromBitmap hGdiImage, hBitmap, 0
Set LoadImage = ConvertToIPicture(hBitmap)
GdipDisposeImage hGdiImage
End If
GdiplusShutdown hGdiPlus
End If
End Function
Public Function ConvertToIPicture(ByVal hPic As Long) As IPicture
Dim uPicInfo As PICTDESC
Dim IID_IDispatch As GUID
Dim IPic As IPicture
Const PICTYPE_BITMAP = 1
With IID_IDispatch
.Data1 = &H7BF80980
.Data2 = &HBF32
.Data3 = &H101A
.Data4(0) = &H8B
.Data4(1) = &HBB
.Data4(2) = &H0
.Data4(3) = &HAA
.Data4(4) = &H0
.Data4(5) = &H30
.Data4(6) = &HC
.Data4(7) = &HAB
End With
With uPicInfo
.Size = Len(uPicInfo)
.Type = PICTYPE_BITMAP
.hPic = hPic
.hPal = 0
End With
OleCreatePictureIndirect uPicInfo, IID_IDispatch, True, IPic
Set ConvertToIPicture = IPic
End Function
© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext