Download as pdf or txt
Download as pdf or txt
You are on page 1of 25

Attribute VB_Name = "mdlGDIPlus2" REM GDIPlus function for VB6 Option Explicit Public Const GUID_IPicture = "{7BF80980-BF32-101A-8BBB-00AA00300CAB}" 'IPicture

Public Enum PicFileType pictypeBMP = 1 pictypeGIF = 2 pictypePNG = 3 pictypeJPG = 4 pictypeTIF = 5 pictypeICO = 6 pictypeUnk = 7 End Enum Private Type T_RGB asRed As Byte asGreen As Byte asBlue As Byte End Type Public Type GUID Data1 As Long Data2 As Integer Data3 As Integer Data4(7) As Byte End Type Public Type TSize X As Double Y As Double End Type Public Type rect Bottom As Long Left As Long Right As Long Top As Long End Type Public Type RECTL Bottom As Long Left As Long Right As Long Top As Long End Type Private Type PICTDESC cbSizeOfStruct As Long PicType As Long hImage As Long xExt As Long yExt As Long End Type Private Type GDIPStartupInput GdiplusVersion As Long DebugEventCallback As Long

SuppressBackgroundThread As Long SuppressExternalCodecs As Long End Type Private Type EncoderParameter UUID As GUID NumberOfValues As Long type As Long Value As Long End Type Private Type EncoderParameters count As Long Parameter As EncoderParameter End Type Public Enum PixelFormat PixelFormat1bppIndexed = &H30101 PixelFormat4bppIndexed = &H30402 PixelFormat8bppIndexed = &H30803 PixelFormat16bppGreyScale = &H101004 PixelFormat16bppRGB555 = &H21005 PixelFormat16bppRGB565 = &H21006 PixelFormat16bppARGB1555 = &H61007 PixelFormat24bppRGB = &H21808 PixelFormat32bppRGB = &H22009 PixelFormat32bppARGB = &H26200A PixelFormat32bppPARGB = &HE200B PixelFormat48bppRGB = &H10300C PixelFormat64bppARGB = &H34400D PixelFormat64bppPARGB = &H1C400E PixelFormatMax = 15 '&HF End Enum Public Enum ColorAdjustType ColorAdjustTypeDefault = 0 ColorAdjustTypeBitmap = 1 ColorAdjustTypeBrush = 2 ColorAdjustTypePen = 3 ColorAdjustTypeText = 4 ColorAdjustTypeCount = 5 ColorAdjustTypeAny = 6 End Enum Public Enum ColorMatrixFlags ColorMatrixFlagsDefault = 0 ColorMatrixFlagsSkipGrays = 1 ColorMatrixFlagsAltGray = 2 End Enum Public Type ColorMatrix m(0 To 4, 0 To 4) As Single End Type Public Enum PaletteFlags PaletteFlagsHasAlpha = &H1 PaletteFlagsGrayScale = &H2 PaletteFlagsHalftone = &H4 End Enum Public Type ColorPalette flags As PaletteFlags count As Long

Entries(0 To 255) As Long End Type Private Enum DitherType DitherTypeNone = 0 DitherTypeSolid = 1 DitherTypeOrdered4x4 = 2 DitherTypeOrdered8x8 = 3 DitherTypeOrdered16x16 = 4 DitherTypeOrdered91x91 = 5 DitherTypeSpiral4x4 = 6 DitherTypeSpiral8x8 = 7 DitherTypeDualSpiral4x4 = 8 DitherTypeDualSpiral8x8 = 9 DitherTypeErrorDiffusion = 10 End Enum Public Enum PaletteType PaletteTypeCustom = 0 PaletteTypeOptimal = 1 PaletteTypeFixedBW = 2 PaletteTypeFixedHalftone8 = 3 PaletteTypeFixedHalftone27 = 4 PaletteTypeFixedHalftone64 = 5 PaletteTypeFixedHalftone125 = 6 PaletteTypeFixedHalftone216 = 7 PaletteTypeFixedHalftone252 = 8 PaletteTypeFixedHalftone256 = 9 End Enum Public Enum GpUnit UnitWorld = 0 UnitDisplay = 1 UnitPixel = 2 UnitPoint = 3 UnitInch = 4 UnitDocument = 5 UnitMillimeter = 6 End Enum Public Type RGBQUAD rgbBlue As Byte rgbGreen As Byte rgbRed As Byte rgbReserved As Byte End Type Public Type COLORBYTES BlueByte As Byte GreenByte As Byte RedByte As Byte AlphaByte As Byte End Type Public Type COLORLONG longval As Long End Type Public Type BitmapData Width As Long Height As Long stride As Long PixelFormat As Long ' ' ' ' ' ' ' World coordinate (non-physical unit) Variable -- for PageTransform only Each unit is one device pixel. Each unit is a printer's point, or 1/72 inch. Each unit is 1 inch. Each unit is 1/300 inch. Each unit is 1 millimeter.

scan0 As Long Reserved As Long End Type Public Enum ImageLockMode ImageLockModeRead = &H1 ImageLockModeWrite = &H2 ImageLockModeUserInputBuf = &H4 End Enum 'Nur GDI+1.1: Private Type SharpenParameters Radius As Single Amount As Single End Type 'Nur GDI+1.1: Private Type BlurParameters Radius As Single ExpandEdges As Long End Type Private Declare Function LoadLibrary Lib "kernel32.dll" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long Private Declare Function FreeLibrary Lib "kernel32.dll" (ByVal hLibModule As Long) As Long Private Declare Function GetProcAddress Lib "kernel32.dll" (ByVal hModule As Long, ByVal lpProcName As String) As Long Private Declare Function GetModuleHandle Lib "kernel32.dll" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long Private Declare Function GetModuleFileName Lib "kernel32.dll" Alias "GetModuleFileNameA" (ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long Private Declare Function OleCreatePictureIndirect Lib "olepro32.dll" (lpPictDesc As PICTDESC, riid As GUID, ByVal fPictureOwnsHandle As Long, IPic As IPicture) As Long Private Declare Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pCLSID As GUID) As Long Private Declare Function GlobalAlloc Lib "kernel32" (ByVal uFlags As Long, ByVal dwBytes As Long) As Long Private Declare Function GlobalSize Lib "kernel32.dll" (ByVal hMem As Long) As Long Private Declare Function GlobalLock Lib "kernel32.dll" (ByVal hMem As Long) As Long Private Declare Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As Long) As Long Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (ByRef Destination As Any, ByRef Source As Any, ByVal Length As Long) Private Declare Sub MoveMemory Lib "kernel32" Alias "RtlMoveMemory" (ByVal Destination As Long, ByRef Source As Byte, ByVal Length As Long) Private Declare Function CreateStreamOnHGlobal Lib "ole32" (ByVal hGlobal As Long, ByVal fDeleteOnRelease As Long, ByRef ppstm As Any) As Long Private Declare Function GetHGlobalFromStream Lib "ole32.dll" (ByVal pstm As Any, ByRef phglobal As Long) As Long Private Declare Function GetDesktopWindow Lib "user32.dll" () As Long Private Declare Function GetClientRect Lib "user32.dll" (ByVal hWnd As Long, ByRef lpRect As rect) As Long

Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long Private Declare Function CreateBitmap Lib "gdi32" (ByVal nWidth As Long, ByVal nHeight As Long, ByVal nPlanes As Long, ByVal nBitCount As Long, lpBits As Any) As Long Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long Private Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long Private Declare Function GetDeviceCaps Lib "gdi32" (ByVal hdc As Long, ByVal nIndex As Long) As Long Private Declare Function PatBlt Lib "gdi32" (ByVal hdc As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal dwRop As Long) As Long Private Declare Function ExtractAssociatedIcon Lib "shell32.dll" Alias "ExtractAssociatedIconA" (ByVal hInst As Long, ByVal lpIconPath As String, lpiIcon As Long) As Long Public Declare Function LockWindowUpdate Lib "user32.dll" (ByVal hwndLock As Long) As Long Private Declare Function GdiplusStartup Lib "gdiplus.dll" (token As Long, inputbuf As GDIPStartupInput, Optional ByVal outputbuf As Long = 0) As Long Private Declare Function GdiplusShutdown Lib "gdiplus.dll" (ByVal token As Long) As Long Private Declare Function GdipCreateBitmapFromFile Lib "gdiplus.dll" (ByVal FileName As Long, BITMAP As Long) As Long Public Declare Function GdipCreateBitmapFromScan0 Lib "gdiplus" (ByVal Width As Long, ByVal Height As Long, ByVal stride As Long, ByVal PixelFormat As Long, scan0 As Any, BITMAP As Long) As Long Private Declare Function GdipCreateFromHDC Lib "gdiplus.dll" (ByVal hdc As Long, GpGraphics As Long) As Long Public Declare Function GdipGetImageGraphicsContext Lib "gdiplus" (ByVal Image As Long, graphics As Long) As Long Private Declare Function GdipDeleteGraphics Lib "gdiplus.dll" (ByVal graphics As Long) As Long Private Declare Function GdipDrawImageRect Lib "gdiplus.dll" (ByVal graphics As Long, ByVal Image As Long, ByVal X As Single, ByVal Y As Single, ByVal Width As Single, ByVal Height As Single) As Long Public Declare Function GdipGraphicsClear Lib "gdiplus" (ByVal graphics As Long, ByVal LColor As Long) As Long Public Declare Function GdipSetCompositingQuality Lib "gdiplus" (ByVal graphics As Long, ByVal CompositingQlty As Long) As Long Public Declare Function GdipCreateImageAttributes Lib "gdiplus" (imageattr As Long) As Long Public Declare Function GdipDrawImageRectRectI Lib "gdiplus" (ByVal graphics As Long, ByVal Image As Long, ByVal dstx As Long, ByVal dsty As Long, ByVal dstwidth As Long, ByVal dstheight As Long, ByVal srcx As Long, ByVal srcy As Long, ByVal srcwidth As Long, ByVal srcheight As Long, ByVal srcUnit As GpUnit, Optional ByVal imageAttributes As Long = 0, Optional ByVal callback As Long = 0, Optional ByVal callbackData As Long = 0) As Long Public Declare Function GdipDisposeImageAttributes Lib "gdiplus" (ByVal imageattr As Long) As Long Public Declare Function GdipSetImageAttributesColorKeys Lib "gdiplus" (ByVal imageattr As Long, ByVal ClrAdjType As ColorAdjustType, ByVal enableFlag As Long, ByVal colorLow As Long, ByVal colorHigh As Long) As Long Public Declare Function GdipCloneImageAttributes Lib "gdiplus" (ByVal imageattr As Long, cloneImageattr As Long) As Long

Public Declare Function GdipResetImageAttributes Lib "gdiplus" (ByVal imageattr As Long, ByVal ClrAdjType As ColorAdjustType) As Long Public Declare Function GdipSetImageAttributesColorMatrix Lib "gdiplus" (ByVal imageattr As Long, ByVal ClrAdjType As ColorAdjustType, ByVal enableFlag As Long, colourMatrix As ColorMatrix, grayMatrix As Any, ByVal flags As ColorMatrixFlags) As Long Public Declare Function GdipSetImageAttributesGamma Lib "gdiplus" (ByVal imageattr As Long, ByVal ClrAdjType As ColorAdjustType, ByVal enableFlag As Long, ByVal gamma As Single) As Long 'Public Declare Function GdipSetImageAttributesRemapTable Lib "gdiplus" (ByVal imageattr As Long, ByVal ClrAdjType As ColorAdjustType, ByVal enableFlag As Long, ByVal mapSize As Long, map As ColorMap) As Long 'Public Declare Function GdipSetImageAttributesWrapMode Lib "gdiplus" (ByVal imageattr As Long, ByVal wrap As WrapMode, ByVal argb As Long, ByVal bClamp As Long) As Long Public Declare Function GdipGetImageAttributesAdjustedPalette Lib "gdiplus" (ByVal imageattr As Long, colorPal As ColorPalette, ByVal ClrAdjType As ColorAdjustType) As Long Public Declare Function GdipGetImagePixelFormat Lib "gdiplus" (ByVal Image As Long, PixelFormat As Long) As Long Public Declare Function GdipGetImagePalette Lib "gdiplus" (ByVal Image As Long, palette As ColorPalette, ByVal size As Long) As Long Public Declare Function GdipSetImagePalette Lib "gdiplus" (ByVal Image As Long, palette As ColorPalette) As Long Public Declare Function GdipGetImagePaletteSize Lib "gdiplus" (ByVal Image As Long, size As Long) As Long Public Declare Function GdipBitmapLockBits Lib "gdiplus" (ByVal BITMAP As Long, rect As RECTL, ByVal flags As ImageLockMode, ByVal PixelFormat As Long, lockedBitmapData As BitmapData) As Long Public Declare Function GdipBitmapUnlockBits Lib "gdiplus" (ByVal BITMAP As Long, lockedBitmapData As BitmapData) As Long Private Declare Function GdipDisposeImage Lib "gdiplus.dll" (ByVal Image As Long) As Long Private Declare Function GdipCreateHBITMAPFromBitmap Lib "gdiplus.dll" (ByVal BITMAP As Long, hbmReturn As Long, ByVal background As Long) As Long Public Declare Function GdipCreateHICONFromBitmap Lib "gdiplus" (ByVal BITMAP As Long, hbmReturn As Long) As Long Private Declare Function GdipGetImageThumbnail Lib "gdiplus.dll" (ByVal Image As Long, ByVal thumbWidth As Long, ByVal thumbHeight As Long, thumbImage As Long, Optional ByVal callback As Long = 0, Optional ByVal callbackData As Long = 0) As Long Private Declare Function GdipCreateBitmapFromHBITMAP Lib "gdiplus.dll" (ByVal hbm As Long, ByVal hpal As Long, BITMAP As Long) As Long Private Declare Function GdipCreateBitmapFromHICON Lib "gdiplus" (ByVal hicon As Long, BITMAP As Long) As Long Private Declare Function GdipGetImageWidth Lib "gdiplus.dll" (ByVal Image As Long, Width As Long) As Long Private Declare Function GdipGetImageHeight Lib "gdiplus.dll" (ByVal Image As Long, Height As Long) As Long Private Declare Function GdipSaveImageToFile Lib "gdiplus.dll" (ByVal Image As Long, ByVal FileName As Long, clsidEncoder As GUID, encoderParams As Any) As Long Private Declare Function GdipSaveImageToStream Lib "gdiplus.dll" (ByVal Image As Long, ByVal stream As IUnknown, clsidEncoder As GUID, encoderParams As Any) As Long Private Declare Function GdipLoadImageFromStream Lib "gdiplus.dll" (ByVal stream As IUnknown, Image As Long) As Long 'NUR GDI+1.1 !!!:

Private Declare Function GdipCreateEffect Lib "gdiplus.dll" (ByVal cid1 As Long, ByVal cid2 As Long, ByVal cid3 As Long, ByVal cid4 As Long, Effect As Long) As Long Private Declare Function GdipSetEffectParameters Lib "gdiplus.dll" (ByVal Effect As Long, params As Any, ByVal size As Long) As Long Private Declare Function GdipBitmapApplyEffect Lib "gdiplus.dll" (ByVal Image As Long, ByVal Effect As Long, ByVal roi As Long, ByVal useAuxData As Long, ByVal auxData As Long, ByVal auxDataSize As Long) As Long Private Declare Function GdipDeleteEffect Lib "gdiplus.dll" (ByVal Effect As Long) As Long Public Declare Function GdipInitializePalette Lib "gdiplus" (ByVal palette As Long, ByVal APaletteType As PaletteType, ByVal optimalColors As Long, ByVal useTransparentColor As Long, ByVal BITMAP As Long) As Long Private Declare Function GdipBitmapConvertFormat Lib "gdiplus.dll" (ByVal Image As Long, ByVal Format As PixelFormat, ByVal ADitherType As DitherType, ByVal APaletteType As PaletteType, ByRef palette As ColorPalette, ByVal alphaThresholdPercent As Single) As Long

Private lGDIP As Long Private hMod As Long Private iEffect As Long Public bIsGdip11 As Boolean Public sfrmPreview As String Private arrCalcMX(4, 4) As Double, dblMatrixSum As Double Function IsGDIPInstalled(Optional bShowMessage As Boolean = True, Optional bhMod As Boolean) As Boolean Dim lAddr As Long If hMod <> 0 Then Exit Function hMod = LoadLibrary(CurrentProject.Path & "\gdiplus.dll") If hMod = 0 Then hMod = LoadLibrary(SysCmd(acSysCmdAccessDir) & "\gdiplus.dll") If hMod = 0 Then hMod = LoadLibrary("gdiplus.dll") If hMod = 0 Then If bShowMessage Then MsgBox "GDIPlus.dll konnte nicht gefunden werden", vbCritical Else IsGDIPInstalled = True lAddr = GetProcAddress(hMod, "GdipCreateEffect") If lAddr = 0 Then If bShowMessage Then MsgBox "GDIPlus.dll liegt in der Version 1.0 vor." & vbCrLf & _ "Fr einige Funktionen wird GDI+1.1 bentigt" & vbCrLf & _ "(Z.B. fr Schrfen der Bilder)." & vbCrLf & _ "Diese Funktionen sind nun deaktiviert.", vbExclamation, "Hinweis" Else bIsGdip11 = True End If End If If (hMod <> 0) And (bhMod = False) Then FreeLibrary hMod hMod = 0 End If End Function Sub InitGDIP() Dim TGDP As GDIPStartupInput

If lGDIP <> 0 Then ShutDownGDIP IsGDIPInstalled False, True TGDP.GdiplusVersion = 1 GdiplusStartup lGDIP, TGDP End Sub Sub ShutDownGDIP() If lGDIP <> 0 Then GdiplusShutdown lGDIP lGDIP = 0 End If If hMod <> 0 Then FreeLibrary hMod hMod = 0 End If End Sub Function LoadPicturePlus(sFilename As String, Optional bForceGDIP As Boolean = True) As StdPicture Dim hBmp As Long Dim hPic As Long If Not bForceGDIP Then Select Case GetFileExt(sFilename) Case "bmp", "gif", "jpg", "jpeg" Set LoadPicturePlus = stdole.LoadPicture(sFilename) Exit Function End Select End If If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromFile(StrPtr(sFilename), hPic) = 0 Then GdipCreateHBITMAPFromBitmap hPic, hBmp, 0& If hBmp <> 0 Then Set LoadPicturePlus = BitmapToPicture(hBmp) GdipDisposeImage hPic End If End If End Function Function ResampleImage(ByVal Image As Picture, ByVal Width As Long, ByVal Height As Long, _ Optional bSharpen As Boolean = True) As StdPicture Dim ret As Long Dim lbitmap As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If Image.type = 1 Then ret = GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) Else ret = GdipCreateBitmapFromHICON(Image.Handle, lbitmap) End If If ret = 0 Then Dim lThumb As Long Dim hBitmap As Long ret = GdipGetImageThumbnail(lbitmap, Width, Height, lThumb, 0, 0) If ret = 0 Then If bSharpen And bIsGdip11 Then

iEffect = 0 On Error Resume Next ret = CreateSharpenEffect If iEffect <> 0 Then ret = SetSharpenParameters(1, 90) If ret = 0 Then GdipBitmapApplyEffect lThumb, iEffect, 0, 0, 0, 0 ret = GdipDeleteEffect(iEffect) Forms(sfrmPreview)!chkSharpen.Enabled = True bIsGdip11 = True Else Forms(sfrmPreview)!chkSharpen.Enabled = False bIsGdip11 = False End If End If If Image.type = 3 Then 'Image-Type 3 heit : Icon! ret = GdipCreateHICONFromBitmap(lThumb, hBitmap) Set ResampleImage = BitmapToPicture(hBitmap, True) Else ret = GdipCreateHBITMAPFromBitmap(lThumb, hBitmap, 0) Set ResampleImage = BitmapToPicture(hBitmap) End If GdipDisposeImage lThumb End If GdipDisposeImage lbitmap End If End Function Function MakeThumb(ByVal Image As Picture, Width As Long, Height As Long, Optional BackColor As Long = 8421504) As StdPicture Dim ret As Long Dim lbitmap As Long Dim lGraph As Long Dim hdc As Long Dim hBmp As Long Dim hBrush As Long Dim X As Long, Y As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function ret = GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) If ret = 0 Then GdipGetImageWidth lbitmap, X GdipGetImageHeight lbitmap, Y hdc = CreateCompatibleDC(0) hBmp = CreateBitmap(Width, Width, GetDeviceCaps(hdc, 14), GetDeviceCaps(hdc, 12), ByVal 0&) hBmp = SelectObject(hdc, hBmp) hBrush = CreateSolidBrush(BackColor) hBrush = SelectObject(hdc, hBrush) PatBlt hdc, 0, 0, Width, Height, &HF00021 'Modus PATCOPY DeleteObject SelectObject(hdc, hBrush) ret = GdipCreateFromHDC(hdc, lGraph) ret = GdipDrawImageRect(lGraph, lbitmap, (Width - X) / 2, (Height Y) / 2, X, Y) hBmp = SelectObject(hdc, hBmp) Set MakeThumb = BitmapToPicture(hBmp) DeleteDC hdc GdipDisposeImage lbitmap GdipDeleteGraphics lGraph

End If End Function Function BlitImageToDC(ByVal Image As Picture, hdc As Long, X As Long, Y As Long) As Boolean Dim ret As Long Dim lGraph As Long Dim lbitmap As Long Dim Width As Long, Height As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If hdc = 0 Then Exit Function If Image Is Nothing Then Exit Function ret = GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) If lbitmap = 0 Then Exit Function ret = GdipCreateFromHDC(hdc, lGraph) If lGraph = 0 Then Exit Function GdipGetImageWidth lbitmap, Width GdipGetImageHeight lbitmap, Height ret = GdipDrawImageRect(lGraph, lbitmap, X, Y, Width / 3, Height / 3) GdipDisposeImage lbitmap GdipDeleteGraphics lGraph End Function Function MergeImages(ByVal Image1 As Picture, ByVal Image2 As Picture, _ Optional delta As Single = 0.5, _ Optional bMaxScreen As Boolean = True) As StdPicture Dim lbitmap As Long, lBitmap1 As Long, lBitmap2 As Long, lGraph As Long Dim H As Long, W As Long, H1 As Long, H2 As Long, W1 As Long, W2 As Long Dim imgAttr As Long, imgAttr2 As Long, hBmp As Long Dim arrCM As ColorMatrix Dim siz As TSize Dim ret As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function ret = GdipCreateBitmapFromHBITMAP(Image1.Handle, 0, lBitmap1) ret = GdipCreateBitmapFromHBITMAP(Image2.Handle, 0, lBitmap2) GdipGetImageHeight lBitmap1, H1 GdipGetImageHeight lBitmap2, H2 GdipGetImageWidth lBitmap1, W1 GdipGetImageWidth lBitmap2, W2 H = H1 W = W1 If H2 > H Then H = H2 If W2 > W Then W = W2 If bMaxScreen Then siz = GetScreenRes If siz.X < W Then H = H * siz.X / W: W = siz.X If siz.Y < H Then W = W * siz.Y / H: H = siz.Y End If ret = GdipCreateBitmapFromScan0(CLng(W), CLng(H), 0, &H22009, ByVal 0&, lbitmap)

ret = GdipGetImageGraphicsContext(lbitmap, lGraph) ret = GdipCreateImageAttributes(imgAttr) ret = GdipCreateImageAttributes(imgAttr2) With arrCM .m(0, 0) = 1 .m(1, 1) = 1 .m(2, 2) = 1 .m(3, 3) = delta .m(4, 4) = 1 End With ret = GdipSetImageAttributesColorMatrix(imgAttr, ColorAdjustTypeBitmap, 1, arrCM, 0&, ColorMatrixFlagsDefault) arrCM.m(3, 3) = 1 - delta ret = GdipSetImageAttributesColorMatrix(imgAttr2, ColorAdjustTypeBitmap, 1, arrCM, 0&, ColorMatrixFlagsDefault) ret = GdipDrawImageRectRectI(lGraph, lBitmap1, (W - W1) \ 2, (H - H1) \ 2, W1, H1, 0, 0, W1, H1, UnitPixel, imgAttr, 0, 0) ret = GdipDrawImageRectRectI(lGraph, lBitmap2, (W - W2) \ 2, (H - H2) \ 2, W2, H2, 0, 0, W2, H2, UnitPixel, imgAttr2, 0, 0) GdipCreateHBITMAPFromBitmap lbitmap, hBmp, 0& Set MergeImages = BitmapToPicture(hBmp) GdipDisposeImageAttributes imgAttr GdipDisposeImage lbitmap GdipDisposeImage lBitmap1 GdipDisposeImage lBitmap2 GdipDeleteGraphics lGraph End Function '? SaveImage(OverlayImages(LoadPicture("e:\sascha2.bmp"),LoadPicture("e:\dev_em ail.bmp"),0.6,10,500,0&),"e:\overlay.jpg",pictypeJPG ) Function OverlayImages(ByVal ImageMain As Picture, ByVal ImageOverlay As Picture, _ ByVal alpha As Single, X As Long, Y As Long, _ Optional TransColor As Long = -1) As StdPicture Dim lBitmap1 As Long, lBitmap2 As Long, lGraph As Long Dim H1 As Long, H2 As Long, W1 As Long, W2 As Long Dim imgAttr As Long, imgAttr2 As Long, hBmp As Long Dim arrCM As ColorMatrix Dim ret As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function ret = GdipCreateBitmapFromHBITMAP(ImageMain.Handle, 0, lBitmap1) ret = GdipCreateBitmapFromHBITMAP(ImageOverlay.Handle, 0, lBitmap2) GdipGetImageHeight lBitmap1, H1 GdipGetImageHeight lBitmap2, H2 GdipGetImageWidth lBitmap1, W1 GdipGetImageWidth lBitmap2, W2 If (W2 > W1) Or (H2 > H1) Then GdipDisposeImage lBitmap1 GdipDisposeImage lBitmap2 Exit Function End If

ret = GdipGetImageGraphicsContext(lBitmap1, lGraph) ret = GdipCreateImageAttributes(imgAttr) With arrCM .m(0, 0) = 1 .m(1, 1) = 1 .m(2, 2) = 1 .m(3, 3) = alpha .m(4, 4) = 1 End With ret = GdipSetImageAttributesColorMatrix(imgAttr, ColorAdjustTypeBitmap, 1, arrCM, 0&, ColorMatrixFlagsDefault) If TransColor > -1 Then ret = GdipCreateImageAttributes(imgAttr2) ret = GdipSetImageAttributesColorKeys(imgAttr2, ColorAdjustTypeBitmap, 1&, ByVal TransColor, ByVal TransColor) End If ' ret = GdipSetCompositingQuality(lGraph, ByVal 3&) ret = GdipDrawImageRectRectI(lGraph, lBitmap2, X, Y, W2, H2, 0, 0, W2, H2, UnitPixel, _ IIf(TransColor > -1, imgAttr2, imgAttr), 0, 0) GdipCreateHBITMAPFromBitmap lBitmap1, hBmp, 0& Set OverlayImages = BitmapToPicture(hBmp) GdipDisposeImageAttributes imgAttr GdipDisposeImageAttributes imgAttr2 GdipDisposeImage lBitmap1 GdipDisposeImage lBitmap2 GdipDeleteGraphics lGraph End Function Function GetImageSize(ByVal Image As Picture) As TSize Dim ret As Long Dim lbitmap As Long Dim X As Long, Y As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If Image Is Nothing Then Exit Function ret = GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) If ret = 0 Then GdipGetImageHeight lbitmap, Y GdipGetImageWidth lbitmap, X GetImageSize.X = CDbl(X) GetImageSize.Y = CDbl(Y) GdipDisposeImage lbitmap End If End Function Function SaveImage(ByRef Image As StdPicture, sFile As String, _ PicType As PicFileType, Optional Quality As Byte = 80) As Boolean Dim lbitmap As Long Dim TEncoder As GUID Dim ret As Long Dim TParams As EncoderParameters Dim sType As String If PicType = pictypeICO Then

MsgBox "Speichern im ICO-Format nicht untersttzt.", vbCritical, "mdlGDIPLUS/SaveImage" Exit Function End If If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then Select Case PicType Case pictypeBMP: sType = "{557CF400-1A04-11D3-9A73-0000F81EF32E}" Case pictypeGIF: sType = "{557CF402-1A04-11D3-9A73-0000F81EF32E}" Case pictypePNG: sType = "{557CF406-1A04-11D3-9A73-0000F81EF32E}" Case pictypeJPG: sType = "{557CF401-1A04-11D3-9A73-0000F81EF32E}" Case pictypeTIF: sType = "{557cf405-1a04-11d3-9a73-0000f81ef32e}" End Select CLSIDFromString StrPtr(sType), TEncoder TParams.count = 0 Select Case PicType Case pictypeJPG TParams.count = 1 With TParams.Parameter ' Quality CLSIDFromString StrPtr("{1D5BE4B5-FA4A-452D-9CDD5DB35105E7EB}"), .UUID .NumberOfValues = 1 .type = 4 .Value = VarPtr(CLng(Quality)) End With Case pictypeGIF If bIsGdip11 Then Dim TPalette As ColorPalette TParams.count = 1 TPalette.count = 256 TPalette.flags = PaletteFlagsHasAlpha ret = GdipInitializePalette( _ ByVal VarPtr(TPalette), PaletteTypeOptimal, 256&, 0&, lbitmap) If ret = 0 Then ret = GdipBitmapConvertFormat( _ lbitmap, PixelFormat8bppIndexed, DitherTypeErrorDiffusion - 1, PaletteTypeOptimal, TPalette, 0) End If Case pictypeTIF TParams.count = 1 With TParams.Parameter 'Kompression CLSIDFromString StrPtr("{E09D739D-CCD4-44EE-8EBA3FBF8BE4FC58}"), .UUID .NumberOfValues = 1 .type = 4 .Value = VarPtr(2&) 'LZW-Kompression; Andere Werte: 'RLE=5; CCITT3=3; CCITT4=4 End With End Select ret = GdipSaveImageToFile(lbitmap, StrPtr(sFile), TEncoder, TParams) GdipDisposeImage lbitmap SaveImage = (Dir(sFile) <> "") End If End Function Sub GeoTiffToJpeg(arrTIFF() As Byte) Dim lbitmap As Long

Dim lBM As Long Dim hBitmap As Long Dim lGraph As Long Dim RCT As RECTL Dim BD As BitmapData Dim H As Long, W As Long Dim X As Long, Y As Long Dim bytes() As Long Dim i As Long, j As Long, D As Long, DD As Double, acol() As Long, TRGB1 As T_RGB, TRGB2 As T_RGB Dim ret As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Sub With RCT .Left = 0 .Top = 6000 .Right = 6000 .Bottom = 0 ReDim bytes(1 To 6000, 1 To 6000) End With With BD .Width = 6000 .Height = 6000 .PixelFormat = PixelFormat32bppARGB .stride = 4 * 6000 .scan0 = VarPtr(bytes(0, 0)) End With ret = GdipCreateBitmapFromScan0(CLng(6000), CLng(6000), 0, PixelFormat32bppARGB, ByVal 0&, lBM) ret = GdipBitmapLockBits(lBM, RCT, ImageLockModeRead Or ImageLockModeUserInputBuf Or ImageLockModeWrite, PixelFormat32bppARGB, BD) ret = GdipBitmapUnlockBits(lBM, BD) Dim TEncoder As GUID Dim TParams As EncoderParameters Dim sType As String sType = "{557CF401-1A04-11D3-9A73-0000F81EF32E}" TParams.count = 1 With TParams.Parameter ' Quality CLSIDFromString StrPtr("{1D5BE4B5-FA4A-452D-9CDD-5DB35105E7EB}"), .UUID .NumberOfValues = 1 .type = 4 .Value = VarPtr(CLng(80)) End With ret = GdipSaveImageToFile(lBM, StrPtr(sFile), TEncoder, TParams) GdipDisposeImage lBM ShutDownGDIP End Sub '? SaveImage(ImageDrawFrame(LoadPicture("e:\sascha2.bmp"),rgb(0,0,0),rgb(255,25 5,255),20), "e:\sascha2_blue.jpg", pictypeJPG) Function ImageDrawFrame(Image As StdPicture, Optional Color1 As Long, _ Optional Color2 As Long, Optional FrameWidth As Long = 1) As StdPicture

Dim lbitmap As Long Dim lBM As Long Dim hBitmap As Long Dim lGraph As Long Dim RCT As RECTL Dim BD As BitmapData Dim H As Long, W As Long Dim X As Long, Y As Long Dim bytes() As Long Dim i As Long, j As Long, D As Long, DD As Double, acol() As Long, TRGB1 As T_RGB, TRGB2 As T_RGB Dim ret As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then ret = GdipGetImageWidth(lbitmap, W) ret = GdipGetImageHeight(lbitmap, H) W = W + FrameWidth * 2 H = H + FrameWidth * 2 With RCT .Left = 0 .Top = H 'Vertauscht!! .Right = W .Bottom = 0 'Vertauscht!! ReDim bytes(W, H) End With With BD .Width = W .Height = H .PixelFormat = PixelFormat32bppARGB .stride = 4 * CLng(.Width + 1) .scan0 = VarPtr(bytes(0, 0)) End With ret = GdipCreateBitmapFromScan0(CLng(W), CLng(H), 0, PixelFormat32bppARGB, ByVal 0&, lBM) ret = GdipGetImageGraphicsContext(lBM, lGraph) ret = GdipGraphicsClear(lGraph, &HFFFFFFFF) ret = GdipBitmapLockBits(lBM, RCT, ImageLockModeRead Or ImageLockModeUserInputBuf Or ImageLockModeWrite, PixelFormat32bppARGB, BD) ReDim acol(FrameWidth) TRGB1 = UnRGB(Color1) TRGB2 = UnRGB(Color2) For D = 1 To FrameWidth DD = 1 + (FrameWidth - 1) * (((D - 1) / (FrameWidth - 1)) ^ 1.2) acol(D) = RGB2ARGB(RGB(TRGB1.asRed * ((DD - 1) / (FrameWidth 1)) + TRGB2.asRed * ((FrameWidth - DD) / (FrameWidth - 1)), _ TRGB1.asGreen * ((DD - 1) / (FrameWidth - 1)) + TRGB2.asGreen * ((FrameWidth - DD) / (FrameWidth - 1)), _ TRGB1.asBlue * ((DD - 1) / (FrameWidth - 1)) + TRGB2.asBlue * ((FrameWidth - DD) / (FrameWidth - 1)))) Next D On Error Resume Next For D = 1 To FrameWidth For X = D To W - D bytes(X, D) = acol(D) bytes(X, H - D) = acol(D) Next X For Y = D To H - D

bytes(D, Y) = acol(D) bytes(W - D, Y) = acol(D) Next Y Next D ret = GdipBitmapUnlockBits(lBM, BD) ret = GdipDrawImageRect(lGraph, lbitmap, FrameWidth, FrameWidth, W FrameWidth * 2, H - FrameWidth * 2) ret = GdipCreateHBITMAPFromBitmap(lBM, hBitmap, 0) Set ImageDrawFrame = BitmapToPicture(hBitmap) GdipDisposeImage lbitmap GdipDisposeImage lBM GdipDeleteGraphics lGraph End If Erase bytes() End Function Function BrightnessContrast(Image As StdPicture, Optional Brightness As Single, Optional Contrast As Single) As StdPicture Dim lbitmap As Long Dim lbitmapRet As Long Dim hBitmap As Long Dim lGraph As Long Dim H As Long, W As Long Dim imgAttr As Long Dim arrCM As ColorMatrix Dim sDiff As Single Dim ret As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function ret = GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) GdipGetImageHeight lbitmap, H GdipGetImageWidth lbitmap, W ret = GdipCreateBitmapFromScan0(CLng(W), CLng(H), 0, &H22009, ByVal 0&, lbitmapRet) ret = GdipGetImageGraphicsContext(lbitmapRet, lGraph) ret = GdipCreateImageAttributes(imgAttr) If Brightness < -1 Then Brightness = -1 If Brightness > 1 Then Brightness = 1 If Contrast < -1 Then Contrast = -1 If Contrast > 1 Then Contrast = 1 sDiff = (Brightness / 2) - (Contrast / 2) With arrCM .m(0, 0) = 1 + Contrast: .m(0, 4) = Brightness + sDiff .m(1, 1) = 1 + Contrast: .m(1, 4) = Brightness + sDiff .m(2, 2) = 1 + Contrast: .m(2, 4) = Brightness + sDiff .m(3, 3) = 1 .m(4, 4) = 1 End With ret = GdipSetImageAttributesColorMatrix(imgAttr, ColorAdjustTypeBitmap, 1, arrCM, 0&, ColorMatrixFlagsDefault) ret = GdipDrawImageRectRectI(lGraph, lbitmap, 0, 0, W, H, 0, 0, W, H, UnitPixel, imgAttr, 0, 0) GdipCreateHBITMAPFromBitmap lbitmapRet, hBitmap, 0& Set BrightnessContrast = BitmapToPicture(hBitmap)

GdipDisposeImageAttributes imgAttr GdipDisposeImage lbitmap GdipDisposeImage lbitmapRet GdipDeleteGraphics lGraph End Function Function SetSaturation(Image As StdPicture, Saturation As Single) As StdPicture Dim lbitmap As Long Dim hBitmap As Long Dim RCT As RECTL Dim BD As BitmapData Dim H As Long, W As Long Dim X As Long, Y As Long Dim bytes() As Long Dim i As Long, j As Long Dim ret As Long Dim col1 As Long, r1 As Double, g1 As Double, b1 As Double, sgray As Double Dim ii As Long, jj As Long Dim lMask As Long If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then ret = GdipGetImageWidth(lbitmap, W) ret = GdipGetImageHeight(lbitmap, H) With RCT .Left = 0 .Top = H .Right = W .Bottom = 0 End With ReDim bytes(W, H) With BD .Width = W .Height = H .PixelFormat = PixelFormat32bppARGB .stride = 4 * CLng(.Width + 1) .scan0 = VarPtr(bytes(0, 0)) End With ret = GdipBitmapLockBits(lbitmap, RCT, ImageLockModeRead Or ImageLockModeUserInputBuf Or ImageLockModeWrite, PixelFormat32bppARGB, BD) lMask = &HFF000000 For X = 0 To W For Y = 0 To H col1 = bytes(X, Y) And Not lMask r1 = col1 \ 256 \ 256 g1 = (col1 \ 256) And &HFF b1 = bytes(X, Y) And &HFF sgray = (b1 + g1 + r1) / 3 r1 = (sgray * (1 - Saturation) + r1 * Saturation) g1 = (sgray * (1 - Saturation) + g1 * Saturation) b1 = (sgray * (1 - Saturation) + b1 * Saturation) If r1 > 255 Then r1 = 255 If r1 < 0 Then r1 = 0 If g1 > 255 Then g1 = 255 If g1 < 0 Then g1 = 0 If b1 > 255 Then b1 = 255 If b1 < 0 Then b1 = 0

bytes(X, Y) = RGB2ARGB(RGB(r1, g1, b1)) Next Y Next X ret = GdipBitmapUnlockBits(lbitmap, BD) ret = GdipCreateHBITMAPFromBitmap(lbitmap, hBitmap, 0) Set SetSaturation = BitmapToPicture(hBitmap) GdipDisposeImage lbitmap End If ShutDownGDIP Erase bytes() End Function Function ImageAutoEquilize(Image As StdPicture) As StdPicture Dim lbitmap As Long Dim hBitmap As Long Dim RCT As RECTL Dim BD As BitmapData Dim H As Long, W As Long Dim X As Long, Y As Long Dim bytes() As Long Dim matrix(4, 4) As Long Dim i As Long, j As Long Dim ret As Long Dim col1 As Long, r1 As Double, g1 As Double, b1 As Double Dim r1max As Double, g1max As Double, b1max As Double Dim r1min As Double, g1min As Double, b1min As Double Dim r1d As Double, g1d As Double, b1d As Double Dim r1f As Double, g1f As Double, b1f As Double Dim lum As Double, lummax As Double, lummin As Double Dim lMask As Long Dim T As Double If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function T = Timer If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then ret = GdipGetImageWidth(lbitmap, W) ret = GdipGetImageHeight(lbitmap, H) With RCT .Left = 0 .Top = H 'Vertauscht!! .Right = W .Bottom = 0 'Vertauscht!! End With ReDim bytes(W, H) With BD .Width = W .Height = H .PixelFormat = PixelFormat32bppARGB .stride = 4 * CLng(.Width + 1) .scan0 = VarPtr(bytes(0, 0)) End With ret = GdipBitmapLockBits(lbitmap, RCT, ImageLockModeRead Or ImageLockModeUserInputBuf Or ImageLockModeWrite, PixelFormat32bppARGB, BD) lMask = &HFF000000 lummin = 10000 'Histogramm For X = 2 To W - 2

For Y = 2 To H - 2 col1 = bytes(X, Y) And Not lMask r1 = col1 \ 256 \ 256 g1 = (col1 \ 256) And &HFF b1 = bytes(X, Y) And &HFF lum = r1 + g1 + b1 If lum > lummax Then lummax = lum r1max = r1: g1max = g1: b1max = b1 End If If lum < lummin Then lummin = lum r1min = r1: g1min = g1: b1min = b1 End If Next Y Next X r1d = r1min g1d = g1min b1d = b1min If r1max <> r1min Then r1f = 256 / (r1max - r1min) Else r1f = 1 If g1max <> g1min Then g1f = 256 / (g1max - g1min) Else g1f = 1 If b1max <> b1min Then b1f = 256 / (b1max - b1min) Else b1f = 1 'Korrektur For X = 0 To W For Y = 0 To H col1 r1 = g1 = b1 = = bytes(X, Y) And Not lMask col1 \ 256 \ 256 (col1 \ 256) And &HFF bytes(X, Y) And &HFF

r1 = (r1 - r1d) * r1f g1 = (g1 - g1d) * g1f b1 = (b1 - b1d) * b1f If r1 > 255 Then r1 = 255 If r1 < 0 Then r1 = 0 If g1 > 255 Then g1 = 255 If g1 < 0 Then g1 = 0 If b1 > 255 Then b1 = 255 If b1 < 0 Then b1 = 0 bytes(X, Y) = RGB2ARGB(RGB(r1, g1, b1)) Next Y Next X ret = GdipBitmapUnlockBits(lbitmap, BD) ret = GdipCreateHBITMAPFromBitmap(lbitmap, hBitmap, 0) Set ImageAutoEquilize = BitmapToPicture(hBitmap) GdipDisposeImage lbitmap End If MsgBox "Finished in " & Round(Timer - T, 3) & " s" ShutDownGDIP Erase bytes() End Function '? SaveImage(ImageEffectMatrix(LoadPicture("e:\sascha2.bmp"),"Sharpen lite"), "e:\sascha2_blue.jpg", pictypeJPG)

Function ImageEffectMatrix(Image As StdPicture, sEffect As String) As StdPicture Dim lbitmap As Long Dim hBitmap As Long Dim RCT As RECTL Dim BD As BitmapData Dim H As Long, W As Long Dim X As Long, Y As Long Dim bytes() As Long Dim matrix(4, 4) As Long Dim i As Long, j As Long Dim ret As Long Dim T As Double Dim col1 As Long, r1 As Double, g1 As Double, b1 As Double Dim ii As Long, jj As Long Dim lMask As Long T = Timer If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then ret = GdipGetImageWidth(lbitmap, W) ret = GdipGetImageHeight(lbitmap, H) With RCT .Left = 0 .Top = H 'Vertauscht!! .Right = W .Bottom = 0 'Vertauscht!! End With ReDim bytes(W, H) With BD .Width = W .Height = H .PixelFormat = PixelFormat32bppARGB .stride = 4 * CLng(.Width + 1) .scan0 = VarPtr(bytes(0, 0)) End With ret = GdipBitmapLockBits(lbitmap, RCT, ImageLockModeRead Or ImageLockModeUserInputBuf Or ImageLockModeWrite, PixelFormat32bppARGB, BD) Set_Matrix sEffect lMask = &HFF000000 For X = 2 To W - 2 For Y = 2 To H - 2 For i = -2 To 2 CopyMemory matrix(0, 2 + i), bytes(X - 2, Y + i), 25 Next i For ii = 0 To 4 For jj = 0 To 4 col1 = matrix(ii, jj) And Not lMask r1 = r1 + arrCalcMX(ii, jj) * (col1 \ 256 \ 256) g1 = g1 + arrCalcMX(ii, jj) * ((col1 \ 256) And &HFF) b1 = b1 + arrCalcMX(ii, jj) * (matrix(ii, jj) And &HFF) Next r1 = g1 = b1 = Next jj ii r1 / dblMatrixSum: If r1 < 0 Then r1 = 0 g1 / dblMatrixSum: If g1 < 0 Then g1 = 0 b1 / dblMatrixSum: If b1 < 0 Then b1 = 0

If r1 > 255 Then r1 = 255 If r1 < 0 Then r1 = 0 If g1 > 255 Then g1 = 255 If g1 < 0 Then g1 = 0 If b1 > 255 Then b1 = 255 If b1 < 0 Then b1 = 0 bytes(X, Y) = RGB2ARGB(RGB(r1, g1, b1)) Next Y Next X ret = GdipBitmapUnlockBits(lbitmap, BD) ret = GdipCreateHBITMAPFromBitmap(lbitmap, hBitmap, 0) Set ImageEffectMatrix = BitmapToPicture(hBitmap) GdipDisposeImage lbitmap End If ShutDownGDIP Erase bytes() Debug.Print (Timer - T) End Function Private Sub Set_Matrix(sEffect As String) Dim X As Long, Y As Long, sum As Double Dim rs As DAO.Recordset Set rs = DBEngine(0)(0).OpenRecordset("SELECT * FROM tblMatrix WHERE [Effekt]='" & sEffect & "'", dbOpenSnapshot) For X = 0 To 4 For Y = 0 To 4 arrCalcMX(X, Y) = rs("M" & CStr(X) & CStr(Y)) Next Y Next X dblMatrixSum = rs("Sum") rs.Close Set rs = Nothing End Sub Function ArrayFromPicture(ByVal Image As Picture, PicType As PicFileType, Optional Quality As Byte = 80) As Byte() Dim lbitmap As Long Dim TEncoder As GUID Dim ret As Long Dim TParams As EncoderParameters Dim sType As String Dim IStm As stdole.IUnknown If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function If GdipCreateBitmapFromHBITMAP(Image.Handle, 0, lbitmap) = 0 Then Select Case PicType 'CLSID des GDIP-Format-Encoders whlen: Case pictypeBMP: sType = "{557CF400-1A04-11D3-9A73-0000F81EF32E}" Case pictypeGIF: sType = "{557CF402-1A04-11D3-9A73-0000F81EF32E}" Case pictypePNG: sType = "{557CF406-1A04-11D3-9A73-0000F81EF32E}" Case pictypeJPG: sType = "{557CF401-1A04-11D3-9A73-0000F81EF32E}" End Select CLSIDFromString StrPtr(sType), TEncoder TParams.count = 0 Select Case PicType Case pictypeJPG TParams.count = 1 With TParams.Parameter

CLSIDFromString StrPtr("{1D5BE4B5-FA4A-452D-9CDD5DB35105E7EB}"), .UUID .NumberOfValues = 1 .type = 4 .Value = VarPtr(Quality) End With Case pictypeGIF If bIsGdip11 Then Dim TPalette As ColorPalette TParams.count = 1 TPalette.count = 256 TPalette.flags = PaletteFlagsHasAlpha ret = GdipInitializePalette(ByVal VarPtr(TPalette), 1&, 256&, 0&, lbitmap) If ret = 0 Then ret = GdipBitmapConvertFormat(lbitmap, 198659, 9&, 1&, TPalette, 0) End If Case pictypeTIF TParams.count = 1 With TParams.Parameter CLSIDFromString StrPtr("{E09D739D-CCD4-44EE-8EBA3FBF8BE4FC58}"), .UUID .NumberOfValues = 1 .type = 4 .Value = VarPtr(2&) End With End Select ret = CreateStreamOnHGlobal(0&, 1, IStm) 'Stream erzeugen ret = GdipSaveImageToStream(lbitmap, IStm, TEncoder, TParams) If ret = 0 Then Dim hMem As Long, LSize As Long, lpMem As Long Dim abData() As Byte ret = GetHGlobalFromStream(IStm, hMem) 'Speicher-Handle aus Stream erhalten If ret = 0 Then LSize = GlobalSize(hMem) lpMem = GlobalLock(hMem) 'Zugriff auf Speicher erhalten ReDim abData(LSize - 1) 'Array entspr. dimensionieren CopyMemory abData(0), ByVal lpMem, LSize GlobalUnlock hMem 'Speicher wieder sperren ArrayFromPicture = abData 'Ergebnis End If Set IStm = Nothing End If GdipDisposeImage lbitmap End If End Function Public Function ArrayToPicture(ByRef PicBin() As Byte) As Picture Dim IStm As stdole.IUnknown Dim size As Long Dim hMem As Long Dim lpMem As Long Dim lbitmap As Long Dim hBmp As Long Dim ret As Long 'Stream lschen 'GDIP-Image-Speicher freigeben

If lGDIP = 0 Then InitGDIP: If lGDIP = 0 Then Exit Function size = UBound(PicBin) + 1 hMem = GlobalAlloc(2, size) 'Speicher im RAM allozieren (Gre wie Array) If hMem = 0 Then Exit Function lpMem = GlobalLock(hMem) 'Speicher entsperren If lpMem <> 0 Then MoveMemory ByVal lpMem, PicBin(0), size 'Array im Speicherblock bertragen GlobalUnlock hMem 'Speicher wieder sperren ret = CreateStreamOnHGlobal(hMem, 1, IStm) 'Stream erzeugen aus Speicherblock If ret = 0 Then 'OK, GDIP starten: ret = GdipLoadImageFromStream(IStm, lbitmap) If ret = 0 Then GdipCreateHBITMAPFromBitmap lbitmap, hBmp, 0& If hBmp <> 0 Then Set ArrayToPicture = BitmapToPicture(hBmp) End If End If GdipDisposeImage lbitmap End If GlobalFree hMem End If End Function 'Nur GDI+1.1! Private Function CreateSharpenEffect() As Long CreateSharpenEffect = GdipCreateEffect(&H63CBF3EE, &H402CC526, &HC562718F, &H4251BF40, iEffect) End Function 'Nur GDI+1.1! Private Function CreateBlurEffect() As Long CreateBlurEffect = GdipCreateEffect(&H633C80A4, &H482B1843, &H28BEF29E, &HD4FDC534, iEffect) End Function 'Nur GDI+1.1! Private Function SetSharpenParameters(ByVal Radius As Single, ByVal Amount As Single) As Long Dim sp As SharpenParameters sp.Radius = Radius ' 0 bis 255 sp.Amount = Amount ' 0 bis 100 SetSharpenParameters = GdipSetEffectParameters(iEffect, sp, Len(sp)) End Function 'Nur GDI+1.1! Private Function SetBlurParameters(ByVal Radius As Single) As Long Dim bp As BlurParameters bp.Radius = Radius ' 0 bis 255 bp.ExpandEdges = 1 SetBlurParameters = GdipSetEffectParameters(iEffect, bp, Len(bp)) End Function Public Function GetIconPic(sFilename As String) As StdPicture Dim lIcon As Long

lIcon = ExtractAssociatedIcon(0, sFilename, 1) If lIcon <> 0 Then Set GetIconPic = BitmapToPicture(lIcon, True) End Function Public Function GetScreenRes() As TSize Dim r As rect Call GetClientRect(GetDesktopWindow, r) GetScreenRes.X = r.Right GetScreenRes.Y = r.Top End Function Function BitmapToPicture(ByVal hBmp As Long, Optional bIsIcon As Boolean = False) As Picture Dim TPicConv As PICTDESC, UID As GUID With TPicConv If bIsIcon Then .cbSizeOfStruct .PicType = 3 Else .cbSizeOfStruct .PicType = 1 End If .hImage = hBmp End With

= 16 'PicType Icon = Len(TPicConv) 'PicType Bitmap

CLSIDFromString StrPtr(GUID_IPicture), UID OleCreatePictureIndirect TPicConv, UID, True, BitmapToPicture End Function Private Function ColorSetAlpha(ByVal LColor As Long, ByVal alpha As Byte) As Long Dim bytestruct As COLORBYTES Dim result As COLORLONG result.longval = LColor LSet bytestruct = result bytestruct.AlphaByte = alpha LSet result = bytestruct ColorSetAlpha = result.longval End Function Private Function GetRGBFromGDIP(ByVal LColor As Long) As Long Dim argb As COLORBYTES CopyMemory argb, LColor, 4 GetRGBFromGDIP = RGB(argb.RedByte, argb.GreenByte, argb.BlueByte) End Function Private Function RGB2ARGB(ByVal LColor As Long) As Long Dim rgbq As RGBQUAD Dim bytestruct As COLORBYTES CopyMemory rgbq, LColor, 4 With bytestruct .AlphaByte = 255 .BlueByte = rgbq.rgbRed

.GreenByte = rgbq.rgbGreen .RedByte = rgbq.rgbBlue End With CopyMemory RGB2ARGB, bytestruct, 4 End Function Public Function UnRGB(lRGB As Long) As T_RGB UnRGB.asRed = (lRGB And 255) UnRGB.asGreen = (lRGB And 65280) \ 256 UnRGB.asBlue = lRGB \ 65536 End Function Private Dim Dim Dim Sub ShowhModFile() hmod2 As Long sDLL As String n As Long

hmod2 = GetModuleHandle("gdiplus.dll") If hmod2 <> 0 Then sDLL = String(255, 0) n = GetModuleFileName(hmod2, sDLL, 255) If n <> 0 Then Debug.Print Left(sDLL, n) End If End If End Sub

You might also like