Registriert seit: 19.05.2016
	
 Version(en): 365
	 
 
	
	
		Hallo beisammen,
  ich hätte eine Frage. Wie kann man eine von mehreren Grafiken, die in einem Tabellenblatt abgelegt sind, je nach Bedingung in einer Userform ablegen. Die Grafik soll also nicht aus derselben Ordner-Struktur, wie die Arbeitsmappe gerufen werden. Sondern aus einem Tabellenblatt (Tabelle2) dirket in die Userform eingefügt werden, je nachdem welchen Steuerelement man nutzt.
  Hat hierzu jemand eine Idee oder Beispiel?
  Besten Dank und viele Grüße
  Andreas
	 
	
	
	
	
 
 
	
	
	
		
	Registriert seit: 22.11.2019
	
 Version(en): 365
	 
 
	
	
		Hallo Andreas, mit folgenden zwei Code-Versionen kannst Du Bilder, die auf einem Excelblatt liegen in Deine Userform in ein Image-Control laden. Einmal nach Angabe der Zeilennummer, in dessen Feld die gewünschte Grafik liegt oder nach dem Bildnamen, ganz wie gewünscht. In der anliegenden Datei ist noch mal der Code und ein weiteres Beispiel zum Laden eines Tabellenbereichs in ein Userform-Image. Der Code ist sowohl für alte 32- als auch für neue 32/64-Bit verwendbar. Schau mal, ob Du das auf Deine Gegebenheiten adaptieren kannst.
  
  BildinUserform.xlsb (Größe: 265 KB / Downloads: 26)
 Code: 
 
 Option Explicit
  #If VBA7 Then   Private Declare PtrSafe Function OleCreatePictureIndirect Lib "oleaut32.dll" ( _           ByRef PicDesc As PIC_DESC, ByRef RefIID As GUID, _           ByVal fPictureOwnsHandle As LongPtr, ByRef IPic As IPictureDisp) As Long   Private Declare PtrSafe Function CopyImage Lib "user32" ( _           ByVal handle As LongPtr, ByVal un1 As Long, ByVal n1 As Long, _           ByVal n2 As Long, ByVal un2 As Long) As LongPtr   Private Declare PtrSafe Function IsClipboardFormatAvailable Lib "user32" ( _           ByVal wFormat As Long) As Long   Private Declare PtrSafe Function SetClipboardData Lib "user32" (ByVal wFormat As Long, _           ByVal hMem As LongPtr) As LongPtr   Private Declare PtrSafe Function GetClipboardData Lib "user32" ( _           ByVal wFormat As Long) As LongPtr   Private Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hWnd As LongPtr) As Long   Private Declare PtrSafe Function CloseClipboard Lib "user32" () As Long   Private Declare PtrSafe Function EmptyClipboard Lib "user32" () As Long   Private Declare PtrSafe Function RegisterClipboardFormat Lib "user32" _           Alias "RegisterClipboardFormatA" (ByVal lpString As String) As Long      Private Type PIC_DESC        lSize As Long        lType As Long        hPic  As LongPtr        hPal  As LongPtr   End Type   Dim hPic  As LongPtr    #Else   Private Declare Function OleCreatePictureIndirect Lib "oleaut32.dll" ( _           ByRef PicDesc As PIC_DESC, ByRef RefIID As GUID, _           ByVal fPictureOwnsHandle As Long, ByRef IPic As IPictureDisp) As Long   Private Declare Function CopyImage Lib "user32" ( _           ByVal handle As Long, ByVal un1 As Long, ByVal n1 As Long, _           ByVal n2 As Long, ByVal un2 As Long) As Long   Private Declare Function IsClipboardFormatAvailable Lib "user32" ( _           ByVal wFormat As Long) As Long   Private Declare  Function SetClipboardData Lib "user32" (ByVal wFormat As Long, _           ByVal hMem As Long) As Long   Private Declare Function GetClipboardData Lib "user32" ( _           ByVal wFormat As Long) As Long   Private Declare Function OpenClipboard Lib "user32" (ByVal hWnd As Long) As Long   Private Declare Function CloseClipboard Lib "user32" () As Long   Private Declare Function EmptyClipboard Lib "user32" () As Long   Private Declare Function RegisterClipboardFormat Lib "user32" _           Alias "RegisterClipboardFormatA" (ByVal lpString As String) As Long      Private Type PIC_DESC        lSize As Long        lType As Long        hPic  As Long        hPal  As Long   End Type   Dim hPic  As Long
  #End If
  Private Type GUID      Data1 As Long      Data2 As Integer      Data3 As Integer      Data4(0 To 7) As Byte End Type
  Private Const PICTYPE_BITMAP = 1 Private Const CF_BITMAP = 2 Private Const IMAGE_BITMAP = 0 Private Const LR_COPYRETURNORG = &H4
  Sub Paste_Picture_ByPosition(iZeile As Long) ' Fügt ein Bild aus einer Pic-Sammlung über die Zwischenablage in ein _  Userform-Control ein   Dim oPict As IPictureDisp, oShape As Shape   Dim tPicInfo As PIC_DESC, tID_IDispatch As GUID
  ' Bild suchen und in die Zwischenablage kopieren   With ThisWorkbook.Sheets("Tabelle2")              ' Blatt ggf. <<<anpassen>>>       For Each oShape In .Shapes           If oShape.TopLeftCell.Address = .Cells(iZeile, "A").Address Then              oShape.CopyPicture Appearance:=xlScreen, Format:=xlBitmap              DoEvents: Exit For           End If       Next oShape   End With
  ' Bild aus Zwischenablage in das Image einfügen   If IsClipboardFormatAvailable(CF_BITMAP) <> 0 Then      If OpenClipboard(0&) <> 0 Then         hPic = CopyImage(GetClipboardData(CF_BITMAP), _         IMAGE_BITMAP, 0, 0, LR_COPYRETURNORG)         CloseClipboard
          If hPic <> 0 Then            With tID_IDispatch                .Data1 = &H20400                .Data4(0) = &HC0                .Data4(7) = &H46            End With
             With tPicInfo                .lSize = Len(tPicInfo)                .lType = PICTYPE_BITMAP                .hPic = hPic                .hPal = 0            End With
             OleCreatePictureIndirect tPicInfo, tID_IDispatch, 0&, oPict
             If Not oPict Is Nothing Then ' ######### Hier die Userform und Image-Angaben anpassen ########               UserForm1.Image3.Picture = oPict            Else               MsgBox "Das Bild kann nicht angezeigt werden", vbCritical, "Bild einfügen"            End If
          End If      End If   End If
  End Sub
 
 
  Sub Paste_Picture_ByName(sSuch As String) ' Fügt ein Bild aus einer Pic-Sammlung über die Zwischenablage in ein _  Userform-Control ein   Dim oPict As IPictureDisp, oShape As Shape   Dim tPicInfo As PIC_DESC, tID_IDispatch As GUID
  ' Bild suchen und in die Zwischenablage kopieren   With ThisWorkbook.Sheets("Tabelle2")              ' Blatt ggf. <<<anpassen>>>       For Each oShape In .Shapes           If oShape.Name Like sSuch & "*" Then              oShape.CopyPicture Appearance:=xlScreen, Format:=xlBitmap              DoEvents: Exit For           End If       Next oShape   End With
  ' Bild aus Zwischenablage in das Image einfügen   If IsClipboardFormatAvailable(CF_BITMAP) <> 0 Then      If OpenClipboard(0&) <> 0 Then         hPic = CopyImage(GetClipboardData(CF_BITMAP), _         IMAGE_BITMAP, 0, 0, LR_COPYRETURNORG)         CloseClipboard         If hPic <> 0 Then            With tID_IDispatch                .Data1 = &H20400                .Data4(0) = &HC0                .Data4(7) = &H46            End With
             With tPicInfo                .lSize = Len(tPicInfo)                .lType = PICTYPE_BITMAP                .hPic = hPic                .hPal = 0            End With
             OleCreatePictureIndirect tPicInfo, tID_IDispatch, 0&, oPict
             If Not oPict Is Nothing Then ' ######### Hier die Userform und Image-Angaben anpassen ########               UserForm1.Image3.Picture = oPict            Else               MsgBox "Das Bild kann nicht angezeigt werden", vbCritical, "Bild einfügen"            End If
          End If      End If   End If End Sub 
 
 _________ viele Grüße Karl-Heinz 
	 
	
	
	
	
 
 
	
	
	
		
	Registriert seit: 06.12.2017
	
 Version(en): diverse
	 
 
	
	
		Hey was für ein geiler Code. Auch wenn sich der Threadersteller noch nicht wieder gemeldet hat, ich kann das gut gebrauchen. Kann ich zwar voraussichtlich erst nächste Woche testen, aber wenn dann Probleme auftauchen sollten meld ich mich. Danke Gruss Igel
	 
	
	
Ich kann nicht alles wissen, aber vieles lernen !   
 
	
	
 
 
	
	
	
		
	Registriert seit: 22.11.2019
	
 Version(en): 365
	 
 
	
	
		Danke Igel für die positive Rückmeldung. Dann viel Spaß und Erfolg beim Ausprobieren.
  Gruß Karl-Heinz
	 
	
	
	
	
 
 
	
	
	
		
	Registriert seit: 19.05.2016
	
 Version(en): 365
	 
 
	
	
		Hallo Karl-Heinz,
  besten Dank. Das ist die perfekte Lösung. Es funktioniert wie es soll. 
  Beste Grüße
  Andreas
	 
	
	
	
	
 
 
	 
 |