Here's some code. I can't site a source for it but its a pretty good demo for what you need.<br><br>At the module level:<br><br>Option Explicit<br><br>Type POINTAPI<br> X As Long<br> Y As Long<br>End Type<br><br>' Change region of a window:<br>Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Boolean) As Long<br>' Precanned region creation functions:<br>Declare Function CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long<br>Declare Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long<br>Declare Function CreateRoundRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long<br>' Polygon region creation functions:<br>Declare Function CreatePolygonRgn Lib "gdi32" (lpPoint As POINTAPI, ByVal nCount As Long, ByVal nPolyFillMode As Long) As Long<br>Declare Function CreatePolyPolygonRgn Lib "gdi32" (lpPoint As POINTAPI, lpPolyCounts As Long, ByVal nCount As Long, ByVal nPolyFillMode As Long) As Long<br>' Polygon type:<br>Public Const WINDING = 2<br>' Region combination:<br>Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long<br> ' Region combination types:<br> Public Const RGN_AND = 1<br> Public Const RGN_COPY = 5<br> Public Const RGN_DIFF = 4<br> Public Const RGN_MAX = RGN_COPY<br> Public Const RGN_MIN = RGN_AND<br> Public Const RGN_OR = 2<br> Public Const RGN_XOR = 3<br> ' Region combination return values:<br> Public Const COMPLEXREGION = 3<br> Public Const SIMPLEREGION = 2<br> Public Const NULLREGION = 1<br><br>' GDI Clear up:<br>Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long<br><br><br>At the Form level:<br><br><br>Option Explicit<br><br>' Shape options:<br>Private Enum EWSShapes<br> wshpNone = 0<br> wshpRoundRectangle = 1<br> wshpEllipse = 2<br> wshpStar = 3<br> wshpLadder = 4<br> wshpHoled = 5<br> wshpWhat = 6<br>End Enum<br>Private m_eShape As EWSShapes<br><br>' Write text on the form:<br>Private 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<br>Private Type RECT<br> left As Long<br> top As Long<br> right As Long<br> bottom As Long<br>End Type<br><br>' Move the windows with the keys:<br>Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long<br> Private Const SC_MOVE = &HF010&<br> Private Const WM_SYSCOMMAND = &H112<br><br>' Move the window with the mouse:<br>Private Declare Function SetCapture Lib "user32" (ByVal hWnd As Long) As Long<br>Private Declare Function ReleaseCapture Lib "user32" () As Long<br>Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long<br>Private m_bMoving As Boolean<br>Private m_sXOffset As Single<br>Private m_sYOffset As Single<br><br>Private Property Get TitleBar() As Boolean<br> TitleBar = (Me.Caption <> ""

<br>End Property<br>Private Property Let TitleBar(ByVal bTitlebar As Boolean)<br> If (TitleBar <> bTitlebar) Then<br> If (bTitlebar) Then<br> Me.Caption = "WindowShaper"<br> Else<br> Me.Caption = ""<br> End If<br> End If<br>End Property<br>Private Property Get Shape() As EWSShapes<br> Shape = m_eShape<br>End Property<br>Private Property Let Shape(ByVal eShape As EWSShapes)<br>Dim hRgn As Long<br>Dim lW As Long<br>Dim lH As Long<br>Dim i As Integer<br>Dim hR1 As Long, hR2 As Long, lR As Long<br>Dim lL As Long, lT As Long, lW1 As Long, lH1 As Long<br> <br> If (eShape <> m_eShape) Then<br> <br> For i = wshpNone To wshpWhat<br> mnuShape(i).Checked = (i = eShape)<br> Next i<br> <br> ' Get size in pixels:<br> lW = Me.Width \ Screen.TwipsPerPixelX<br> lH = Me.Height \ Screen.TwipsPerPixelY<br> <br> ' Create a region of the appropriate shape:<br> Select Case eShape<br> Case wshpNone<br> ' Select a Region = 0 to reset:<br> hRgn = 0<br> Case wshpRoundRectangle<br> ' Simple region:<br> hRgn = CreateRoundRectRgn(0, 0, lW, lH, 64, 64)<br> Case wshpEllipse<br> ' Simple region:<br> hRgn = CreateEllipticRgn(0, 0, lW, lH)<br> Case wshpStar<br> ' A polygon region:<br> Dim tStar(0 To 10) As POINTAPI<br> ' This is not geometrically correct, but gives the idea...<br> tStar(0).X = lW \ 2: tStar(0).Y = 0<br> tStar(1).X = (lW * 2) \ 3: tStar(1).Y = lH \ 3<br> tStar(2).X = lW: tStar(2).Y = tStar(1).Y<br> tStar(3).X = (lW * 9) \ 12: tStar(3).Y = (lH * 7) \ 12<br> tStar(4).X = lW: tStar(4).Y = lH<br> tStar(5).X = lW \ 2: tStar(5).Y = (lH * 9) \ 12<br> tStar(6).X = 0: tStar(6).Y = tStar(4).Y<br> tStar(7).X = (lW * 3) \ 12: tStar(7).Y = tStar(3).Y<br> tStar(8).X = 0: tStar(8).Y = tStar(2).Y<br> tStar(9).X = lW \ 3: tStar(9).Y = tStar(1).Y<br> LSet tStar(10) = tStar(0)<br> hRgn = CreatePolygonRgn(tStar(0), 11, WINDING)<br> Case wshpLadder<br> ' OR Combine two rectangular regions:<br> hR1 = CreateRectRgn(0, 0, lW / 2, lH / 2)<br> hR2 = CreateRectRgn(lW / 2, lH / 2, lW, lH)<br> hRgn = CreateRectRgn(0, 0, 0, 0)<br> ' NB the destination must be a valid region handle before this is called:<br> lR = CombineRgn(hRgn, hR1, hR2, RGN_OR)<br> DeleteObject hR1<br> DeleteObject hR2<br> Case wshpHoled<br> ' Difference Combine two rectangular regions:<br> hR1 = CreateRectRgn(0, 0, lW, lH)<br> hR2 = CreateRectRgn(lW / 4, lH / 4, lW * 3 / 4, lH * 3 / 4)<br> hRgn = CreateRectRgn(0, 0, 0, 0)<br> lR = CombineRgn(hRgn, hR1, hR2, RGN_DIFF)<br> DeleteObject hR1<br> DeleteObject hR2<br> Case wshpWhat<br> ' OR a random set of regions together for rather bizarre shape:<br> hRgn = CreateRectRgn(0, 0, 0, 0)<br> For i = 1 To 5<br> lL = (Rnd * lW + 1)<br> lT = (Rnd * lH + 1)<br> lW1 = (Rnd * lW + 1) \ 2<br> lH1 = (Rnd * lH + 1) \ 2<br> Select Case (i Mod 3)<br> Case 1<br> hR1 = CreateEllipticRgn(lL, lT, lL + lW1, lL + lH1)<br> Case 2<br> hR1 = CreateRoundRectRgn(lL, lT, lL + lW1, lT + lH1, lW1 \ 5, lH1 \ 5)<br> Case Else<br> hR1 = CreateRectRgn(lL, lT, lL + lW1, lT + lH1)<br> End Select<br> lR = CombineRgn(hRgn, hR1, hRgn, RGN_OR)<br> DeleteObject hR1<br> Next i<br> End Select<br> <br> ' Change the region:<br> SetWindowRgn Me.hWnd, hRgn, 1<br> ' We don't need to manage the hRgn object -<br> ' Windows does this for us.<br> <br> ' Store the shape:<br> m_eShape = eShape<br> End If<br>End Property<br><br>Private Sub Form_Load()<br> Randomize Timer<br>End Sub<br><br>Private Sub Form_LostFocus()<br> Form_MouseUp vbLeftButton, 0, 0, 0<br>End Sub<br><br>Private Sub Form_MouseDown(Button As Integer, Shift As Integer, X As Single, Y As Single)<br> Select Case True<br> Case (Button And vbLeftButton) = vbLeftButton<br> ' Set flag saying we're moving:<br> m_bMoving = True<br> ' Determine where the mouse is relative to the top,left of the form:<br> ' The vertical border of the form has a width Width-ScaleWidth\2:<br> m_sXOffset = X + (Me.Width - Me.ScaleWidth) \ 2<br> ' Approximate the horizontal offset due to title bar & horizontal border:<br> m_sYOffset = Y + (Me.Height - Me.ScaleHeight) - (Me.Width - Me.ScaleWidth) \ 2<br> ' Ensure all messages go to this window:<br> SetCapture Me.hWnd<br> Case (Button And vbRightButton) = vbRightButton<br> Me.PopupMenu mnuTop<br> End Select<br>End Sub<br><br>Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)<br>Dim tP As POINTAPI<br> If (m_bMoving) Then<br> ' If we're moving, then place the form on the screen where the mouse is,<br> ' taking into account where we initially clicked on the form:<br> GetCursorPos tP<br> Me.Move tP.X * Screen.TwipsPerPixelX - m_sXOffset, tP.Y * Screen.TwipsPerPixelY - m_sYOffset<br> End If<br>End Sub<br><br>Private Sub Form_MouseUp(Button As Integer, Shift As Integer, X As Single, Y As Single)<br> If (m_bMoving) Then<br> ' Clear capture. We also call this during LostFocus just in case<br> ReleaseCapture<br> m_bMoving = False<br> End If<br>End Sub<br><br><br>Private Sub Form_Paint()<br>Dim sText As String<br>Dim tR As RECT<br>Dim lH As Long<br> <br> ' Show a caption on the form:<br> Me.Cls<br> sText = "Right Click for some Shape Related fun!"<br> tR.right = Me.ScaleWidth \ Screen.TwipsPerPixelX<br> tR.bottom = Me.ScaleHeight \ Screen.TwipsPerPixelY<br> DrawText Me.hdc, sText, Len(sText), tR, (1& Or &H10&)<br> <br>End Sub<br><br>Private Sub Form_Resize()<br> Form_Paint<br>End Sub<br><br>Private Sub mnuRight_Click(Index As Integer)<br>Dim lP As Long<br> Select Case Index<br> Case 0 ' Move<br> ' Emulates clicking the Move option in a system menu:<br> lP = ((Me.left \ Screen.TwipsPerPixelX) And &HFFFF&) ' horiz pos is loword<br> lP = lP + (Me.top \ Screen.TwipsPerPixelY \ &H10000) ' vert pos is hiword<br> SendMessage Me.hWnd, WM_SYSCOMMAND, SC_MOVE, lP<br> Case 2 ' Title bar<br> mnuRight(2).Checked = Not (mnuRight(2).Checked)<br> TitleBar = mnuRight(2).Checked<br> Case 5 ' Exit<br> Unload Me<br> End Select<br>End Sub<br><br>Private Sub mnuShape_Click(Index As Integer)<br> Shape = Index<br>End Sub<br><br><br><br> <p> <br><a href=mailto: > </a><br><a href=
temporary Vorpalcom home page</a><br>Send me suggestions or comments on my current software project.