VBcoders Guest



Don't have an account yet? Register
 


Forgot Password?



This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap

by DiskJunky (16 Submissions)
Category: Graphics
Compatability: VB 6.0
Difficulty: Unknown Difficulty
Originally Published: Tue 15th January 2002
Date Added: Mon 8th February 2021
Rating: (1 Votes)

This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap to RotateBitmap etc. It can draw shapes,

API Declarations


'12/11/2001
'----------------------------------------------
' Author : Eric O'Sullivan
'----------------------------------------------
'Contact : [email protected]
'----------------------------------------------
'Comments :
'This module was made for using api graphics functions in your
'programs. With the following api calls and function and procedures
'written by me, you have to tools to do almost anything. The only api
'function listed here that is not directly used by any piece of code
'in this module is BitBlt. You have the tools to create and manipulate
'graphics, but it is still necessary to display them manually. The
'functions themselves mostly need hDc or a handle to work. You can
'find this hDc in both a forms and pictureboxs' properties. I have
'also set up a data type called BitmapStruc. For my programs, I have
'used this structure almost exclusivly for the graphics. The structure
'holds all the information needed to reference a bitmap created using
'this module (CreateNewBitmap, DeleteBitmap).
'Please keep in mind that any object (bitmap, brush, pen etc) needs to
'be deleted after use or else it will stay in memory until the program is
'finished. Not doing so will eventually cause your program to take up
'ALL your computers recources.
'Also for anyone using optional paramters, it is probably better to use
'a default parameter values to determine whether or not a parameter
'has been passed than the function IsMissing().
'
'Thank you,
'Eric
'----------------------------------------------


Option Explicit


'These functions are sorted alphabetically.
Public Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Public Declare Function ChangeDisplaySettings Lib "user32" Alias "ChangeDisplaySettingsA" (ByRef wef As Any, ByVal i As Long) As Long
Public Declare Function CreateBrushIndirect Lib "gdi32" (lpLogBrush As LogBrush) As Long
Public Declare Function CreateColorSpace Lib "gdi32" Alias "CreateColorSpaceA" (lplogcolorspace As LogColorSpace) As Long
Public Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hDc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Public Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hDc As Long) As Long
Public Declare Function CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Public Declare Function CreateEllipticRgnIndirect Lib "gdi32" (EllRect As Rect) As Long
Public Declare Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LogFont) As Long
Public Declare Function CreatePen Lib "gdi32" (ByVal nPenStyle As Long, ByVal nWidth As Long, ByVal crColor As Long) As Long
Public Declare Function CreatePenIndirect Lib "gdi32" (lpLogPen As LogPen) As Long
Public Declare Function CreateRectRgn Lib "gdi32" (Left As Integer, Top As Integer, Right As Integer, Bottom As Integer) As Long
Public Declare Function CreateSolidBrush Lib "gdi32" (ColorRef As Long) As Long
Public Declare Function DeleteDC Lib "gdi32" (ByVal hDc As Long) As Long
Public Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Public Declare Function DrawAnimatedRects Lib "user32" (ByVal hwnd As Long, ByVal idAni As Long, lprcFrom As Rect, lprcTo As Rect) As Long
Public Declare Function DrawIconEx Lib "user32" (ByVal hDc As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) As Long
Public Declare Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hDc As Long, ByVal lpStr As String, ByVal nCount As Long, lpRect As Rect, ByVal wFormat As Long) As Long
Public Declare Function Ellipse Lib "gdi32" (ByVal hDc As Long, X1 As Integer, Y1 As Integer, X2 As Integer, Y2 As Integer) As Boolean
Public Declare Function EnumDisplaySettings Lib "user32" Alias "EnumDisplaySettingsA" (ByVal A As Long, ByVal B As Long, wef As DEVMODE) As Boolean
Public Declare Function ExtCreatePen Lib "gdi32" (ByVal dwPenStyle As Long, ByVal dwWidth As Long, lplb As LogBrush, ByVal dwStyleCount As Long, lpStyle As Long) As Long
Public Declare Function FillRect Lib "user32" (ByVal hwnd As Long, Fill As Rect, hBrush As Long) As Integer
Public Declare Function FillRgn Lib "gdi32" (ByVal hDc As Long, ByVal HRgn As Long, hBrush As Long) As Boolean
Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Public Declare Function GetActiveWindow Lib "user32" () As Long
Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
Public Declare Function GetBitmapDimensionEx Lib "gdi32" (ByVal hBitmap As Long, lpDimension As SizeType) As Long
Public Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Public Declare Function GetClientRect Lib "user32" (ByVal hwnd As Long, lpRect As Rect) As Long
Public Declare Function GetCursor Lib "user32" () As Long
Public Declare Function GetCursorPos Lib "user32" (lpPoint As PointAPI) As Long
Public Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Public Declare Function GetDesktopWindow Lib "user32" () As Long
Public Declare Function GetDeviceCaps Lib "gdi32" (ByVal hDc As Long, ByVal nIndex As Long) As Long
Public Declare Function GetLastError Lib "kernel32" () As Long
Public Declare Function GetObjectAPI Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, lpObject As Any) As Long
Public Declare Function GetPixel Lib "gdi32" (ByVal hDc As Long, ByVal X As Long, ByVal Y As Long) As Long
Public Declare Function GetTextMetrics Lib "gdi32" Alias "GetTextMetricsA" (ByVal hDc As Long, lpMetrics As TEXTMETRIC) As Long
Public Declare Function GetTickCount Lib "kernel32" () As Long 'very usefull timing function ;)
Public Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long
Public Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As Rect) As Long
Public Declare Function InflateRect Lib "user32" (lpRect As Rect, ByVal X As Long, ByVal Y As Long) As Long
Public Declare Function IntersectRect Lib "user32" (lpDestRect As Rect, lpSrc1Rect As Rect, lpSrc2Rect As Rect) As Long
Public Declare Function LineTo Lib "gdi32" (ByVal hDc As Long, XEnd As Integer, YEnd As Integer) As Boolean
Public Declare Function LoadCursor Lib "user32" Alias "LoadCursorA" (ByVal hInstance As Long, ByVal lpCursorName As Any) As Long
Public Declare Function LoadImage Lib "user32" Alias "LoadImageA" (ByVal hInst As Long, ByVal lpsz As String, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As Long
Public Declare Function MoveToEx Lib "gdi32" (ByVal hDc As Long, X As Integer, Y As Integer, PointAPI) As Boolean
Public Declare Function MulDiv Lib "kernel32" (ByVal nNumber As Long, ByVal nNumerator As Long, ByVal nDenominator As Long) As Long
Public Declare Function OffsetRect Lib "user32" (lpRect As Rect, ByVal X As Long, ByVal Y As Long) As Long
Public 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
Public Declare Function Polygon Lib "gdi32" (ByVal hDc As Long, lpPoint As PointAPI, ByVal nCount As Long) As Long
Public Declare Function Polyline Lib "gdi32" (ByVal hDc As Long, lpPoint As PointAPI, ByVal nCount As Long) As Long
Public Declare Function PolylineTo Lib "gdi32" (ByVal hDc As Long, lppt As PointAPI, ByVal cCount As Long) As Long
Public Declare Function Rectangle Lib "gdi32" (ByVal hwnd As Long, X1 As Integer, Y1 As Integer, X2 As Integer, Y2 As Integer) As Long
Public Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hDc As Long) As Long
Public Declare Function RoundRect Lib "gdi32" (ByVal hDc As Long, ByVal Left As Long, ByVal Top As Long, ByVal Right As Long, ByVal Bottom As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Public Declare Function SelectObject Lib "gdi32" (ByVal hDc As Long, ByVal hObject As Long) As Long
Public Declare Function SetBkColor Lib "gdi32" (ByVal hDc As Long, ByVal crColor As Long) As Long
Public Declare Function SetBkMode Lib "gdi32" (ByVal hDc As Long, ByVal nBkMode As Long) As Long
Public Declare Function SetColorAdjustment Lib "gdi32" (ByVal hDc As Long, lpca As COLORADJUSTMENT) As Long
Public Declare Function SetColorSpace Lib "gdi32" (ByVal hDc As Long, ByVal hcolorspace As Long) As Long
Public Declare Function SetPixel Lib "gdi32" (ByVal hDc As Long, ByVal X As Long, ByVal Y As Long, ByVal crColor As Long) As Long
Public Declare Function SetRect Lib "user32" (lpRect As Rect, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Public Declare Function SetTextColor Lib "gdi32" (ByVal hDc As Long, ByVal crColor As Long) As Long
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Public Declare Function StretchBlt Lib "gdi32" (ByVal hDc As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal nSrcWidth As Long, ByVal nSrcHeight As Long, ByVal dwRop As Long) As Long


'--------------------------------------------------------------------------
'enumerator section
'--------------------------------------------------------------------------

'the direction of the gradient
Public Enum GradientTo
GradHorizontal = 0
GradVertical = 1
End Enum

'in twips or pixels
Public Enum Scaling
InTwips = 0
InPixels = 1
End Enum

'The key values of the mouse buttons
Public Enum MouseKeys
MouseLeft = 1
MouseRight = 2
MouseMiddle = 4
End Enum

'text alignment constants
Public Enum AlignText
vbLeftAlign = 1
vbCentreAlign = 2
vbRightAlign = 3
End Enum

'bitmap flip constants

Rate This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap



'This is a "brute force" alpha blend function. Because it's written in
'vb, this function is not as fast at it might otherwise be in another
'language like C++ or Fox.
'The purpose of the function is to mix the colours of two bitmaps to
'produce a result that looks like both pictures. Think of it as fading
'one picture into another. I get the pixel colour of a point in picture1,
'and the colour of the corresponding pixel in pixture2, find the 'middle'
'colour and put it into the destination bitmap. There are no calls to
'other procedures or functions other than api calls. This is to improve
'speed as all calculations are made internally.
'The parameter BlendAmount MUST be between 1 and 0. If not then
'the value is rounded to 1 or zero.
'However, BlendAmount is ignored if a Mask bitmap has been specified.
'Please note that if the mask used only containts black or white pixels,
'then it is recommended that you use the MergeBitmaps procedure as
'it will process the bitmaps much faster (about 15 to 30 times faster).
'Keep in mind that using a mask bitmap is about 25% slower than
'specifying the blend amount.

Dim TempBmp As BitmapStruc
Dim Result As Long
Dim Col1 As RGBVal
Dim Col2 As RGBVal
Dim BlendCol As RGBVal
Dim MaskCol As RGBVal
Dim CounterX As Long
Dim CounterY As Long
Dim PxlHeight As Integer
Dim PxlWidth As Integer
Dim LngBlendCol As Long
Dim LngCol1 As Long
Dim LngCol2 As Long
Dim LngMaskCol As Long

'first convert the passed values if they need to be converted.
If Measurement = InTwips Then
    'get the pixel height and width values per twips in the current
    'screen resolution.
    PxlHeight = Screen.TwipsPerPixelY
    PxlWidth = Screen.TwipsPerPixelX
    
    'start converting the twip values to pixels
    DestX = DestX / PxlWidth
    Width = Width / PxlWidth
    Pic1X = Pic1X / PxlWidth
    Pic2X = Pic2X / PxlWidth
    DestY = DestY / PxlHeight
    Height = Height / PxlHeight
    Pic1Y = Pic1Y / PxlHeight
    Pic2Y = Pic2Y / PxlHeight
End If

'validate the BlendAmount parameter. it must be a values between 0 and
'1. If the parameter is outside these bounds, then round to nearist
'bounding value (0 or 1)
Select Case BlendAmount
Case Is >= 1
    BlendAmount = 1
    
    'just copy the picture instead of trying to blend it
    Result = BitBlt(DesthDc, DestX, DestY, Width, Height, Pic2hDc, Pic2X, Pic2Y, SRCCOPY)
    Exit Sub
Case Is <= 0
    BlendAmount = 0
    
    'just copy the picture instead of trying to blend it
    Result = BitBlt(DesthDc, DestX, DestY, Width, Height, Pic1hDc, Pic1X, Pic1Y, SRCCOPY)
    Exit Sub
End Select

'create a temperory destination bitmap
TempBmp.Area.Right = Width
TempBmp.Area.Bottom = Height
Call CreateNewBitmap(TempBmp.hDcMemory, TempBmp.hDcBitmap, TempBmp.hDcPointer, TempBmp.Area, DesthDc)

'start going through the 2 source bitmaps and blending the colours.
For CounterX = 0 To Width
    For CounterY = 0 To Height
        'get the pixel colours
        LngCol1 = GetPixel(Pic1hDc, Pic1X + CounterX, Pic1Y + CounterY)
        LngCol2 = GetPixel(Pic2hDc, Pic2X + CounterX, Pic2Y + CounterY)
        
        'if a blend mask has been specified, then get the blend amount
        'from the bitmap.
        If MaskhDc <> 0 Then
            LngMaskCol = GetPixel(MaskhDc, CounterX, CounterY)
            
            'convert the long value into the blend amount
            MaskCol.Blue = LngMaskCol \ 65536
            MaskCol.Green = ((LngMaskCol - (MaskCol.Blue * 65536)) \ 256)
            MaskCol.Red = (LngMaskCol - (MaskCol.Blue * 65536) - (MaskCol.Green * 256))
            
            'now convert rgb value to value between 0 and 1 (divide by 3 for the average rgb and 255 to a value between 1 and 0 (3 * 255 = 765) )
            BlendAmount = (MaskCol.Red + MaskCol.Green + MaskCol.Blue) \ 765
            'BlendAmount = (MaskCol.Red + MaskCol.Green + MaskCol.Blue) * 0.00130718 '(0.00130718954248366 = 1/765)
            'BlendAmount = MaskCol.Blue * 0.00130718
        End If
        
        'convert long values to rgb values
        Col1.Blue = LngCol1 \ 65536
        Col1.Green = ((LngCol1 - (Col1.Blue * 65536)) \ 256)
        Col1.Red = (LngCol1 - (Col1.Blue * 65536) - (Col1.Green * 256))
        Col2.Blue = LngCol2 \ 65536
        Col2.Green = ((LngCol2 - (Col2.Blue * 65536)) \ 256)
        Col2.Red = (LngCol2 - (Col2.Blue * 65536) - (Col2.Green * 256))

        'average the colours by blend amount
        If (Col1.Red <> Col2.Red) Or (Col1.Green <> Col2.Green) Or (Col1.Blue <> Col2.Blue) Then
            BlendCol.Red = Col1.Red - ((Col1.Red - Col2.Red) * BlendAmount)
            BlendCol.Green = Col1.Green - ((Col1.Green - Col2.Green) * BlendAmount)
            BlendCol.Blue = Col1.Blue - ((Col1.Blue - Col2.Blue) * BlendAmount)
        Else
            'there is no point in blending colours that are the same
            BlendCol = Col1
        End If
        
        'convert the BlendCol RGB values to a long
        LngBlendCol = (CLng(BlendCol.Blue) * 65536) + (CLng(BlendCol.Green) * 256) + BlendCol.Red
        
        'set the corresponding pixel colour on the temperory bitmap
        Result = SetPixel(TempBmp.hDcMemory, CounterX, CounterY, LngBlendCol) 'FromRGB(BlendCol.Red, BlendCol.Green, BlendCol.Blue))
    Next CounterY
Next CounterX

'copy the blended pctures to the destination bitmap
Result = BitBlt(DesthDc, DestX, DestY, Width, Height, TempBmp.hDcMemory, 0, 0, SRCCOPY)

'remove the temperory bitmap from memory
Call DeleteBitmap(TempBmp.hDcMemory, TempBmp.hDcBitmap, TempBmp.hDcPointer)
End Sub

Public Sub FlipBitmap(ByVal DesthDc As Long, ByVal DestX As Integer, ByVal DestY As Integer, ByVal Width As Integer, ByVal Height As Integer, ByVal SourcehDc As Long, ByVal SourceX As Integer, ByVal SourceY As Integer, Optional ByVal Orientation As FlipType = FlipHorizontally, Optional ByVal Measurement As Scaling = InPixels)
'This procedure will flip a picture either horizontally or vertically. It
'copies the bitmap eithre row by row or column by column to improve
'speed.

Dim PxlHeight As Byte
Dim PxlWidth As Byte
Dim Counter As Integer
Dim TempBmp As BitmapStruc
Dim Finish As Integer
Dim Result As Long

'convert the twips to pixel values if necessary
If Measurement = InTwips Then
    PxlWidth = Screen.TwipsPerPixelX
    PxlHeight = Screen.TwipsPerPixelY
    
    DestX = DestX / PxlWidth
    Width = Width / PxlWidth
    SourceX = SourceX / PxlWidth
    DestY = DestY / PxlHeight
    Height = Height / PxlHeight
    SourceY = SourceY / PxlHeight
End If

'create the temperory bitmap
TempBmp.Area.Right = Width
TempBmp.Area.Bottom = Height
Call CreateNewBitmap(TempBmp.hDcMemory, TempBmp.hDcBitmap, TempBmp.hDcPointer, TempBmp.Area, SourcehDc)

'define the bounds of the loop depending on the orientation (do I scan
'the bitmap row by row or column by column)
Select Case Orientation
Case FlipHorizontally
    'scan column by column
    Finish = Width - 1
Case FlipVertically
    'scan row by row
    Finish = Height - 1
End Select

For Counter = 0 To Finish
    'copy the row or column into the appropiate section of the bitmap
    If Orientation = FlipHorizontally Then
        'horizontal
        Result = BitBlt(TempBmp.hDcMemory, Finish - Counter, 0, 1, Height, SourcehDc, SourceX + Counter, SourceY, SRCCOPY)
    Else
        'flip vertically
        Result = BitBlt(TempBmp.hDcMemory, 0, Finish - Counter, Width, 1, SourcehDc, SourceX, SourceY + Counter, SRCCOPY)
    End If
Next

'copy the flipped bitmap onto the destination bitmap
Result = BitBlt(DesthDc, DestX, DestY, TempBmp.Area.Right, TempBmp.Area.Bottom, TempBmp.hDcMemory, 0, 0, SRCCOPY)
End Sub

Public Sub RotateBitmap(ByVal DesthDc As Long, ByVal SourcehDc As Long, ByVal Rotate As RotateType, ByVal DestX As Integer, ByVal DestY As Integer, ByVal SourceX As Integer, ByVal SourceY As Integer, ByVal Width As Integer, ByVal Height As Integer, Optional ByVal Measurement As Scaling = InPixels)
'This procedure will rotate a bitmap 90, 180 or 270 degrees.

Dim Result As Long
Dim PxlWidth As Integer
Dim PxlHeight As Integer
Dim CounterX As Integer
Dim CounterY As Integer
Dim TempBmp As BitmapStruc
Dim BitCol As Long

'convert twips values to pixels if necessary
If Measurement = InTwips Then
    PxlHeight = Screen.TwipsPerPixelY
    PxlWidth = Screen.TwipsPerPixelX
    
    'convert values
    DestX = DestX / PxlWidth
    SourceX = SourceX / PxlWidth
    Width = Width / PxlWidth
    DestY = DestY / PxlHeight
    SourceY = SourceY / PxlHeight
    Height = Height / PxlHeight
End If

'create a temperory bitmap to draw on
If Rotate = Rotate180 Then
    'the width and height dimensions are the same
    TempBmp.Area.Bottom = Height
    TempBmp.Area.Right = Width
Else
    'rotate the dimensions 90 degrees
    TempBmp.Area.Bottom = Width
    TempBmp.Area.Right = Height
End If
Call CreateNewBitmap(TempBmp.hDcMemory, TempBmp.hDcBitmap, TempBmp.hDcPointer, TempBmp.Area, DesthDc)

Select Case Rotate
Case RotateRight To RotateLeft
    'rotate bitmap right or left
    For CounterX = 0 To Width
        For CounterY = 0 To Height
            'get the pixel colour
            BitCol = GetPixel(SourcehDc, SourceX + CounterX, SourceY + CounterY)
            
            'copy to appropiate part of the temperory bitmap
            If Rotate = RotateRight Then
                'rotate right
                Result = SetPixel(TempBmp.hDcMemory, Height - CounterY, CounterX, BitCol)
            Else
                'rotate left
                Result = SetPixel(TempBmp.hDcMemory, CounterY, Height - CounterX, BitCol)
            End If
        Next CounterY
    Next CounterX

Case Rotate180
    'rotate bitmap 180 degrees
    
    'we rotate the bitmap 180 degrees by flipping it vertically and
    'horizontally. This is done fastest by calling the FlipBitmap procedure
    Call FlipBitmap(TempBmp.hDcMemory, 0, 0, Width, Height, SourcehDc, SourceX, SourceY)
    Call FlipBitmap(TempBmp.hDcMemory, 0, 0, Width, Height, TempBmp.hDcMemory, 0, 0, FlipVertically)
End Select

'copy the temperory bitmap to the destination Dc at the specified
'co-ordinates
Result = BitBlt(DesthDc, DestX, DestY, TempBmp.Area.Right, TempBmp.Area.Bottom, TempBmp.hDcMemory, 0, 0, SRCCOPY)

'remove the temperory bitmap from memory and exit
Call DeleteBitmap(TempBmp.hDcMemory, TempBmp.hDcBitmap, TempBmp.hDcPointer)
End Sub

Public Sub DrawRect(ByVal hDc As Long, ByVal Colour As Long, ByVal Left As Integer, ByVal Top As Integer, ByVal Right As Integer, ByVal Bottom As Integer, Optional ByVal Measurement As Scaling = InPixels, Optional ByVal Style As Long = BS_SOLID, Optional ByVal Pattern As Long = HS_SOLID)
'this draws a rectangle using the co-ordinates
'and colour given.

Dim StartRect As Rect
Dim RetVal As Long
Dim Junk  As Long
Dim Brush As Long
Dim BrushStuff As LogBrush

If Measurement = InTwips Then
    'convert to pixels
    Left = Left / Screen.TwipsPerPixelX
    Top = Top / Screen.TwipsPerPixelY
    Right = Right / Screen.TwipsPerPixelX
    Bottom = Bottom / Screen.TwipsPerPixelY
End If

StartRect.Top = Top
StartRect.Left = Left
StartRect.Bottom = Bottom
StartRect.Right = Right

BrushStuff.lbColor = Colour
BrushStuff.lbHatch = Pattern
BrushStuff.lbStyle = Style
 
Brush = CreateBrushIndirect(BrushStuff)
Brush = SelectObject(hDc, Brush)
    
RetVal = PatBlt(hDc, Left, Top, (Right - Left), (Bottom - Top), PATCOPY)

'A "Brush" object was created. It must be removed from memory.
Junk = SelectObject(hDc, Brush)
Junk = DeleteObject(Junk)
End Sub

Public Sub DrawRoundRect(ByVal hDc As Long, ByVal Colour As Long, ByVal Left As Integer, ByVal Top As Integer, ByVal Right As Integer, ByVal Bottom As Integer, ByVal EdgeRadius As Integer, Optional ByVal Measurement As Scaling = InPixels, Optional ByVal Style As Long = BS_SOLID, Optional ByVal Pattern As Long = HS_SOLID)

Download this snippet    Add to My Saved Code

This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap Comments

No comments have been posted about This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap . Why not be the first to post a comment about This module contains various api graphics operations from FlipBitmap to BFAlphaBlend to LoadBitmap .

Post your comment

Subject:
Message:
0/1000 characters