Adjan AutoPro

Excel VBA-Userform (Special 02, Proizvod Menadžer)

📝 U ovom specijal video tutorialu radićemo ceo projekt zasnovan na stvarnim potrebama jedne radnje sa bilo kojim proizvodima. Cela svrha je unapređivanje sistema za menadžment prodavanja, izdavanja računa, lakše knjiženje, pracenje stanja količine (lagera), sortiranja i dosta drugih stvari. I najvažnije koristimo telefon kao barkod skener koji je povezan sa našom userform aplikaciom!

Sheet Proizvoda

Klassa Proizvoda

Class Modules “Proizvodi_Class”. Imamo jedan prizvod koji ima sledece properties : Barkod, Naziv, Cena, Količina i Slika i kreiramo class-u sa tim svojstvima:

Option Explicit


Private pBarkod As String
Private pNaziv As String
Private pCena As String
Private pLager As String
Private pSlikaPath As String

Private pSheetProizvoda As Worksheet
Private pSheetTemplateBarkod As String


'------------- BARKOD ------------
Public Property Let barkod(value As Double)
    pBarkod = value
End Property
Public Property Get barkod() As Double
    barkod = pBarkod
End Property

'------------- NAZIV ------------
Public Property Let Naziv(value As String)
    pNaziv = value
End Property
Public Property Get Naziv() As String
    Naziv = pNaziv
End Property

'------------- CENA ------------
Public Property Let Cena(value As String)
    pCena = value
End Property
Public Property Get Cena() As String
    Cena = pCena
End Property

'------------- LAGER ------------
Public Property Let Lager(value As String)
    pLager = value
End Property
Public Property Get Lager() As String
    Lager = pLager
End Property

'------------- SLIKA ------------
Public Property Let SlikaPath(value As String)
    pSlikaPath = value
End Property
Public Property Get SlikaPath() As String
    SlikaPath = pSlikaPath
End Property

'------------- SHEET PROIZVODA ------------
Public Property Set SheetProizvoda(value As Worksheet)
    Set pSheetProizvoda = value
End Property
Public Property Get SheetProizvoda() As Worksheet
    Set SheetProizvoda = pSheetProizvoda
End Property


'------------- SHEET TEMPLATE BERKOD ------------
Public Property Let SheetTemplateBarkod(value As String)
    pSheetTemplateBarkod = value
End Property
Public Property Get SheetTemplateBarkod() As String
    SheetTemplateBarkod = pSheetTemplateBarkod
End Property


' ================================== DODAJ NOV PROIZVOD ==================================
Sub DodajProizvod()
    Dim tempSheet As Worksheet
    Dim newRow As Long
    newRow = Application.WorksheetFunction.CountA(SheetProizvoda.Range("B:B")) + 1

    SheetProizvoda.Cells(newRow, 2).value = barkod
    SheetProizvoda.Cells(newRow, 3).value = Naziv
    SheetProizvoda.Cells(newRow, 4).value = Cena
    SheetProizvoda.Cells(newRow, 7).value = Lager
    
    If SlikaPath <> "" Then
    Application.ScreenUpdating = False
        'Set TempSheet
        Set tempSheet = ActiveSheet
        SheetProizvoda.Activate
        
        'Add Image
        Cells(newRow, 5).Select
        ActiveSheet.Pictures.Insert(SlikaPath).Select
        
        'Format Image
        Selection.ShapeRange.ScaleHeight 0.22, msoFalse, msoScaleFromTopLeft
        Selection.ShapeRange.IncrementLeft 9
        Selection.ShapeRange.IncrementTop 2
        
        ' Rename Image
        Selection.ShapeRange.Name = barkod
        Selection.Name = barkod
        
        ' Image Hyperlink
        ActiveSheet.Hyperlinks.Add Anchor:=Selection.ShapeRange.Item(1), Address:=SlikaPath
        
        'Return Current Sheet
        tempSheet.Activate
        
    SheetProizvoda.Cells(newRow, 6).value = SlikaPath
    Application.ScreenUpdating = True
    Else
    
    End If
        
    
    
    
    MsgBox "Uspesno ste dodali nov prozvod: " & Naziv

End Sub
'==============================================================================================



' ================================== STAMPAJ BARKOD PROIZVODA ==================================
Sub StampajProizvod()
 
    If sheetExist(SheetTemplateBarkod) Then
        Call Macro_DeleteBarcodePrintTemplate
        Call Macro_BarcodePrintTemplate
    Else
        Call Macro_BarcodePrintTemplate
    End If
    
    Sheets(SheetTemplateBarkod).Range("D3") = Naziv
    Sheets(SheetTemplateBarkod).Range("D5") = barkod
    Sheets(SheetTemplateBarkod).Range("D4") = Cena
    Sheets(SheetTemplateBarkod).Range("C6") = "*" & barkod & "*"
    
    
    Call exportAsPdf(SheetTemplateBarkod)
    
End Sub



Function sheetExist(sheetToFind As String) As Boolean
    
    Dim Sheet As Worksheet
    
    sheetExist = False
    For Each Sheet In Worksheets
        If sheetToFind = Sheet.Name Then
            sheetExist = True
        End If
    Next Sheet
    
End Function


Sub exportAsPdf(mySheet As String)

    Dim myFileName As String
    Dim answer As Integer
    
     answer = MsgBox("Da li želite da sacuvate kao PDF ?", vbQuestion + vbYesNo + vbDefaultButton2, "Export As Pdf ??")
      
        If answer = vbYes Then
                    myFileName = Application.GetSaveAsFilename(, FileFilter:="PDF (*.pdf), *.pdf")
                     ActiveSheet.ExportAsFixedFormat Type:=xlTypePDF, Filename:=myFileName, _
                     IncludeDocProperties:=True, IgnorePrintAreas:=False, OpenAfterPublish:=True
        End If

    
End Sub
'==============================================================================================


     


'============================================ VLOOKUP =========================================
 Function VLookup_Naziv(barcode As Double)
    VLookup_Naziv = Application.WorksheetFunction.VLookup(barcode, SheetProizvoda.Range("B2:G1000"), 2, 0)
 End Function
 
 Function VLookup_Cena(barcode As Double)
    VLookup_Cena = Application.WorksheetFunction.VLookup(barcode, SheetProizvoda.Range("B2:G1000"), 3, 0)
 End Function

  Function VLookup_Slika(barcode As Double)
  
  Dim temp As String
  temp = Application.WorksheetFunction.VLookup(barcode, SheetProizvoda.Range("B2:G1000"), 5, 0)
  
  If temp = "" Then
    VLookup_Slika = ThisWorkbook.Path & "\Proizvodi_Images\noimage.jpg"
  Else
   VLookup_Slika = temp
  End If
   
 End Function

  Function VLookup_Lager(barcode As Double)
    VLookup_Lager = Application.WorksheetFunction.VLookup(barcode, SheetProizvoda.Range("B2:G1000"), 6, 0)
 End Function
 
 
 
 
Public Sub updateLager(newLage As Integer, barkod As Double)
    SheetProizvoda.Range("G" & iRow(barkod)) = newLage
End Sub

Function iRow(barkod) As Integer
    iRow = Application.WorksheetFunction.Match(Application.WorksheetFunction.VLookup(barkod, SheetProizvoda.Range("B2:G1000"), 1, 0), SheetProizvoda.Range("B:B"), 0)
End Function
 '=============================================================================================

Dodavanje novog prizvoda

UserForm “frm_ADD”. U ovoj projektu smo radili na dizajnu, pa možete i sami videti kako userforma izgleda pre i posle.

Option Explicit
 
 ' skloni top bar (definicija)
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare PtrSafe Function DrawMenuBar Lib "user32" (ByVal hwnd As Long) As Long
Private Const GWL_STYLE As Long = (-16)
 
 
Dim NovProizvod As Proizvodi_Class
 
 
    ' Colors
    Public blue01_Color As Long
    Public grey01_Color As Long
    Public btn_Color As Long
    Public white_Color As Long
    Public hoverDark_Color As Long



    Dim mouse_down As Boolean
    Dim mouse_starting_X As Double
    Dim mouse_starting_Y As Double




Private Sub UserForm_Initialize()

    Dim frm As Long
    Dim wHandle As Long
    wHandle = FindWindow(vbNullString, Me.Caption)
    frm = GetWindowLong(wHandle, GWL_STYLE)
    SetWindowLong wHandle, -16, 0
    DrawMenuBar wHandle

    Set NovProizvod = New Proizvodi_Class
    Set NovProizvod.SheetProizvoda = Worksheets("ProizvodSheet")

    Call GUI
End Sub

 
Private Sub lbl_Add_Click()


    NovProizvod.barkod = CDbl(tb_ScenBC.Text)
    NovProizvod.Naziv = tb_Naziv.Text
    NovProizvod.Cena = tb_Cena.Text
    NovProizvod.Lager = tb_Lager.Text
    NovProizvod.SlikaPath = tb_SlikaPath.Text
    
    NovProizvod.DodajProizvod
    
End Sub

 
Private Sub Image_Proizvod_Click()

     Dim fName As String
 
     With Application.FileDialog(msoFileDialogFilePicker)
        .AllowMultiSelect = False
        .ButtonName = "Submit"
        .Title = "Selektujete sliku proizvoda"
        .Filters.Add "Image", "*.gif; *.jpg; *.jpeg", 1
        
        If .Show = -1 Then
            tb_SlikaPath = .SelectedItems(1)
            Image_Proizvod.Picture = LoadPicture(.SelectedItems(1))
            Me.Repaint
       Else
              MsgBox "Niste odabrali sliku proizvoda "
       End If
       
    End With

 

End Sub

Private Sub tb_SlikaPath_AfterUpdate()
Image_Proizvod.Picture = LoadPicture(tb_SlikaPath.Text)
End Sub


Private Sub btn_BarkodManual_Click()

    Dim answer As Integer
    
    If tb_ScenBC.Text = "" Then
        answer = MsgBox("Da li zelite da se barkod sam generise?", vbQuestion + vbYesNo + vbDefaultButton2, "Generisanje Barkoda ??")
        If answer = vbYes Then
             Call autoGenerateBarcode
        End If
    Else
        Call makeBarcode
    End If



End Sub


Sub autoGenerateBarcode()

    Dim tempBarkod As String
    tempBarkod = Evaluate("RANDBETWEEN(0000000000000,9999999999999)")
    
    If Application.CountIf(Sheets("ProizvodSheet").Columns(2), tempBarkod) Then
        MsgBox "Doslo je do greske prilikom generisanja barkoda, pokusajte opet!"
    Else
        tb_ScenBC.Text = tempBarkod
        Call makeBarcode
    End If


End Sub


Sub makeBarcode()

    With lbl_barcodeImg
        .Font.Name = "CCode39"
        .Font.Size = 13
        .Caption = "*" + tb_ScenBC.Text + "*"
    End With

End Sub




Private Sub lbl_PrintBarcode_Click()

    NovProizvod.SheetTemplateBarkod = "BarkodTemplate"
    NovProizvod.barkod = CDbl(tb_ScenBC.Text)
    NovProizvod.Naziv = tb_Naziv.Text
    NovProizvod.Cena = tb_Cena.Text

    
    NovProizvod.StampajProizvod


End Sub



Private Sub lbl_Exit_Click()
    Unload Me
End Sub





' ==============================================================================
'                                   GUI
' ==============================================================================

Sub GUI()
    mouse_down = False
    
    frm_ADD.Height = 280

    blue01_Color = RGB(22, 144, 248)
    grey01_Color = RGB(171, 171, 171)
    btn_Color = RGB(50, 52, 77)
    white_Color = RGB(239, 238, 230)
    hoverDark_Color = RGB(103, 103, 105)
    
    Me.BackColor = grey01_Color
    
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    lbl_TopBar.BackColor = btn_Color
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
    lbl_PrintBarcode.BackColor = btn_Color
    lbl_PrintBarcode_Out.BackColor = btn_Color
    ' Dugme ADD
    lbl_Add.ForeColor = white_Color
    lbl_Add.BackColor = btn_Color
    lbl_Add_Out.BackColor = btn_Color
    
    
    Label01.BackColor = blue01_Color
    Label02.BackColor = blue01_Color
    Label03.BackColor = blue01_Color
    Label04.BackColor = blue01_Color
End Sub




Private Sub lbl_Exit_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = white_Color
    lbl_Exit.ForeColor = btn_Color
End Sub


Private Sub lbl_TopBar_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    ' Form Move
    If mouse_down = True Then
        frm_ADD.Left = frm_ADD.Left + (X - mouse_starting_X)
        frm_ADD.Top = frm_ADD.Top + (Y - mouse_starting_Y)
    End If
End Sub





Private Sub lbl_PrintBarcode_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = hoverDark_Color

End Sub
Private Sub lbl_PrintBarcode_Out_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
End Sub



Private Sub lbl_Add_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme ADD
    lbl_Add.ForeColor = hoverDark_Color

End Sub
Private Sub lbl_Add_out_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme ADD
    lbl_Add.ForeColor = white_Color
End Sub



Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
    ' Dugme ADD
    lbl_Add.ForeColor = white_Color
    
End Sub




'---------------------------------------------------------------------------------

Private Sub lbl_TopBar_MouseDown(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    mouse_down = True
    mouse_starting_X = X
    mouse_starting_Y = Y
End Sub


Private Sub lbl_TopBar_MouseUp(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    mouse_down = False
End Sub


Izdavanje računa

Userform “frm_MAIN”. U ovoj userformi dodajumo naše proizvode na listu (račun), popunjavamo podatke o našem klijentu i štampamo račun.

Option Explicit
 
 ' skloni top bar (definicija)
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare PtrSafe Function DrawMenuBar Lib "user32" (ByVal hwnd As Long) As Long
Private Const GWL_STYLE As Long = (-16)
 
  
 
    ' Colors
    Public blue01_Color As Long
    Public grey01_Color As Long
    Public btn_Color As Long
    Public white_Color As Long
    Public hoverDark_Color As Long



    Dim mouse_down As Boolean
    Dim mouse_starting_X As Double
    Dim mouse_starting_Y As Double
    
    
Dim Proizvod As Proizvodi_Class
Dim barkod As Double



 

Private Sub UserForm_Initialize()

    Dim frm As Long
    Dim wHandle As Long
    wHandle = FindWindow(vbNullString, Me.Caption)
    frm = GetWindowLong(wHandle, GWL_STYLE)
    SetWindowLong wHandle, -16, 0
    DrawMenuBar wHandle

    Set Proizvod = New Proizvodi_Class
    Set Proizvod.SheetProizvoda = Worksheets("ProizvodSheet")


    lb_Proizvodi.ColumnCount = 4
    lb_Proizvodi.ColumnWidths = "90,228,36,60"
    
    Call GUI
    
    lbl_Now.Caption = Format(CDate(Now()), "dd.mm.yyyy")
    
    Me.Height = 445

    Call ocistiSve
End Sub



Private Sub btn_BarkodManual_Click()

    If IsNumeric(tb_ScenBC.value) Then
        barkod = CDbl(tb_ScenBC.value)
        Call getProizvod
    Else
        MsgBox "Skenirani barkod nije broj!"
    End If


End Sub


Sub getProizvod()


    If Application.CountIf(Sheets("ProizvodSheet").Columns(2), barkod) = False Then
          MsgBox "Proizvod nije u bazi podataka!"
        Exit Sub
    End If



    tb_Barcod.Text = tb_ScenBC.value
    tb_Naziv.Text = Proizvod.VLookup_Naziv(barkod)
    tb_Cena.Text = Proizvod.VLookup_Cena(barkod)
    tb_Lager.Text = Proizvod.VLookup_Lager(barkod)
    Image_Proizvod.Picture = LoadPicture(Proizvod.VLookup_Slika(barkod))
    
    
    
     Call calculatePrice

End Sub
 
Private Sub tb_Kolicina_Change()
 Call calculatePrice
End Sub


Sub calculatePrice()
    
     If IsNumeric(tb_Kolicina.value) Then
        lbl_Cena.Caption = Format((Val(tb_Kolicina.value) * Val(tb_Cena.value)), "#,##0.0")
    Else
        MsgBox "'Kolicina' nije broj!"
    End If


End Sub




Private Sub lbl_Add_Click()

    Dim lastRow As Integer
    lastRow = lb_Proizvodi.ListCount + 1
    
    lb_Proizvodi.AddItem
        lb_Proizvodi.List(lastRow - 1, 0) = tb_Barcod.Text
        lb_Proizvodi.List(lastRow - 1, 1) = tb_Naziv.Text
        lb_Proizvodi.List(lastRow - 1, 2) = tb_Kolicina.Text
        lb_Proizvodi.List(lastRow - 1, 3) = lbl_Cena.Caption


        
        tb_Lager.Text = Val(tb_Lager.value) - Val(tb_Kolicina.value)

        Call Proizvod.updateLager(Val(tb_Lager.value), barkod)
       
        Call calculateMainPrice
        
        Call ocistiSve
End Sub


Sub ocistiSve()

        tb_Barcod.Text = ""
        tb_Naziv.Text = ""
        tb_Cena.Text = ""
        tb_Lager.Text = ""
        lbl_Cena.Caption = ""
        Image_Proizvod.Picture = LoadPicture(vbNullString)
        
        tb_ScenBC.Text = ""
        tb_ScenBC.SetFocus

End Sub


 



Sub calculateMainPrice()

    Dim MySum As Double
    
    Dim row As Long
    MySum = 0
    
    With lb_Proizvodi
        For row = 0 To .ListCount - 1
            MySum = MySum + .List(row, 3)
        Next row
    End With

    tb_TOTAL.Text = Format(MySum, "#,##0.0")
    
End Sub


 


Private Sub tb_ScenBC_Change()

 If tb_ScenBC.Text = "" Then
        lb_AutoComplite.Visible = False
    End If

End Sub




Private Sub tb_ScenBC_KeyPress(ByVal KeyAscii As MSForms.ReturnInteger)

    Dim i As Integer
    
    lb_AutoComplite.Clear
    
    lb_AutoComplite.Visible = True
    
    For i = 2 To Sheet2.Range("B1000").End(xlUp).row
        If Left(Sheet2.Cells(i, 2), Len(tb_ScenBC.Text)) = tb_ScenBC.Text Then
            lb_AutoComplite.AddItem Sheet2.Cells(i, 2)
        End If
   Next i
    
End Sub


Private Sub lb_AutoComplite_Click()
    tb_ScenBC.Text = lb_AutoComplite.value
    lb_AutoComplite.Visible = False
End Sub






Private Sub lbl_RemuveListItem_Click()

    Dim answer As Integer
    
        If lb_Proizvodi.ListIndex >= 0 Then

            answer = MsgBox("Da li želite da proizvod sa liste?", vbQuestion + vbYesNo + vbDefaultButton2, "Brisanje proizvoda ??")
            
            If answer = vbYes Then
                Call removeAndUpgrade
            End If
            
        Else
            MsgBox "Niste selektovali proizvod!"
        End If

End Sub


Sub removeAndUpgrade()

    Dim newLager As Integer
    Dim i As Integer
    Dim currentBarcode As Double

    
        For i = 0 To lb_Proizvodi.ListCount - 1
        
            If lb_Proizvodi.Selected(i) = True Then
            
                currentBarcode = CDbl(lb_Proizvodi.List(i, 0))
                newLager = Val(lb_Proizvodi.List(i, 2)) + Val(Proizvod.VLookup_Lager(currentBarcode))
                Call Proizvod.updateLager(newLager, currentBarcode)
                 
                lb_Proizvodi.RemoveItem i
                Call calculateMainPrice
                
            End If
            
        Next i



End Sub






Private Sub lbl_PrintRacun_Click()


    Dim ws As Worksheet
    Set ws = ThisWorkbook.Sheets("RacunSheet")

    Call Macro_PripremiNovRacun
    
    
    ws.Range("F3").value = lbl_Now.Caption
    ws.Range("F4").value = tb_BrRacuna.value
    ws.Range("F5").value = rb_KupacId.value
    
    ws.Range("A10").value = tb_Ime.value
    ws.Range("A11").value = tb_Komp.value
    ws.Range("A12").value = tb_Adrs.value
    ws.Range("A13").value = tb_Grad.value
    ws.Range("A14").value = tb_Tel.value

    ws.Range("F34").value = tb_TOTAL.value
    
    Call exportList(ws)
    
 
    Proizvod.exportAsPdf ("RacunSheet")


End Sub



Sub exportList(ws As Worksheet)

    Dim i As Integer
    Dim r As Integer
    r = 17
    
    ' loop through all items in ListBox1
    For i = 0 To Me.lb_Proizvodi.ListCount - 1
    
        ws.Range("A" & r + i) = lb_Proizvodi.List(i, 1)
        ws.Range("E" & r + i) = lb_Proizvodi.List(i, 2)
        ws.Range("F" & r + i) = lb_Proizvodi.List(i, 3)
    
    Next i


End Sub



Private Sub lbl_Down_Click()
    Me.Height = 545
End Sub

 
Private Sub lbl_Up_Click()
    Me.Height = 445
End Sub


 
Private Sub lbl_Exit_Click()
    Unload Me
End Sub



 




' ==============================================================================
'                                   GUI
' ==============================================================================

Sub GUI()
    mouse_down = False
    
    frm_MAIN.Height = 445
    

    blue01_Color = RGB(22, 144, 248)
    grey01_Color = RGB(171, 171, 171)
    btn_Color = RGB(50, 52, 77)
    white_Color = RGB(239, 238, 230)
    hoverDark_Color = RGB(103, 103, 105)
    
    Me.BackColor = grey01_Color
    Frame_Proizvod.BackColor = grey01_Color
    
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    lbl_TopBar.BackColor = btn_Color
    ' Dugme PRINT
    lbl_PrintRacun.ForeColor = white_Color
    lbl_PrintRacun.BackColor = btn_Color
    lbl_PrintRacun_Out.BackColor = btn_Color
    ' Dugme ADD
    lbl_Add.ForeColor = white_Color
    lbl_Add.BackColor = btn_Color
    lbl_Add_Out.BackColor = btn_Color
    
    
    Label01.BackColor = blue01_Color
    Label02.BackColor = blue01_Color
    Label03.BackColor = blue01_Color
    Label04.BackColor = blue01_Color
End Sub




' Mouse hover DARK  [X]
Private Sub lbl_Exit_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_Exit.ForeColor = btn_Color
    lbl_Exit.BackColor = white_Color
End Sub
' Mouse hover BLUE  [X]
Private Sub lbl_TopBar_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
        ' Mouse hover BLUE  [X]
    lbl_Exit.ForeColor = white_Color
    lbl_Exit.BackColor = btn_Color
    
    If mouse_down = True Then
        frm_MAIN.Left = frm_MAIN.Left + (X - mouse_starting_X)
        frm_MAIN.Top = frm_MAIN.Top + (Y - mouse_starting_Y)
    End If
End Sub


' Mouse hover DARK  [Štampaj Racun]
Private Sub lbl_PrintRacun_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_PrintRacun.ForeColor = hoverDark_Color
End Sub
' Mouse hover WHITE  [Štampaj Racun]
Private Sub lbl_PrintRacun_out_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_PrintRacun.ForeColor = white_Color
End Sub
 
 
' Mouse hover DARK  [Dodaj Artikal]
Private Sub lbl_Add_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_Add.ForeColor = hoverDark_Color
End Sub
' Mouse hover WHITE  [Dodaj Artikal]
Private Sub lbl_Add_out_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_Add.ForeColor = white_Color
End Sub
 
  
 
 ' Mouse hover DARK  [User DOWN]
Private Sub lbl_Down_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_Down.ForeColor = hoverDark_Color
End Sub

 ' Mouse hover DARK  [User UP]
Private Sub lbl_Up_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_Up.ForeColor = hoverDark_Color
End Sub



' Mouse hover DARK  [Obrisi]
Private Sub lbl_RemuveListItem_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    lbl_RemuveListItem.ForeColor = hoverDark_Color
End Sub


' Mouse on  USERFORM
Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Mouse hover BLUE  [X]
    lbl_Exit.ForeColor = white_Color
    lbl_Exit.BackColor = btn_Color
    
    ' Mouse hover WHITE  [User DOWN]
    lbl_Down.ForeColor = &HFFFFFF
    ' Mouse hover WHITE  [User UP]
    lbl_Up.ForeColor = &HFFFFFF
    
    ' Mouse hover WHITE  [Obrisi]
    lbl_RemuveListItem.ForeColor = white_Color
End Sub

  ' Mouse hover USERFORM
Private Sub Image_User_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
   ' Mouse hover WHITE  [User DOWN]
    lbl_Down.ForeColor = white_Color
    ' Mouse hover WHITE  [User UP]
    lbl_Up.ForeColor = white_Color
End Sub
 

Private Sub lbl_TopBar_MouseUp(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
     mouse_down = False
End Sub



Private Sub lbl_TopBar_MouseDown(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    mouse_down = True
    mouse_starting_X = X
    mouse_starting_Y = Y
End Sub


Izdavanje računa

Userforma “frm_PRINT_BC”. Ovde štampamo label (tikete) od našeg prizvoda, glavna svrha je da imamo barkod koga kasnije možemo da skeniramo.

Option Explicit
 
 ' skloni top bar (definicija)
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare PtrSafe Function DrawMenuBar Lib "user32" (ByVal hwnd As Long) As Long
Private Const GWL_STYLE As Long = (-16)
 
 
Dim Proizvod As Proizvodi_Class
 
 
    ' Colors
    Public blue01_Color As Long
    Public grey01_Color As Long
    Public btn_Color As Long
    Public white_Color As Long
    Public hoverDark_Color As Long



    Dim mouse_down As Boolean
    Dim mouse_starting_X As Double
    Dim mouse_starting_Y As Double


     Dim barcode As Double





Private Sub UserForm_Initialize()

    Dim frm As Long
    Dim wHandle As Long
    wHandle = FindWindow(vbNullString, Me.Caption)
    frm = GetWindowLong(wHandle, GWL_STYLE)
    SetWindowLong wHandle, -16, 0
    DrawMenuBar wHandle
    
    Set Proizvod = New Proizvodi_Class
    Set Proizvod.SheetProizvoda = Worksheets("ProizvodSheet")
    
    Call GUI
End Sub

Private Sub btn_BarcodeManual_Click()
  
    If IsNumeric(tb_ScanBC.value) Then
        barcode = CDbl(tb_ScanBC.value)
        Call getProduct
    Else
        MsgBox "Skenirani bar kod nije broj!"
    End If
    
    lb_AutoComplite.Visible = False
  
End Sub





Sub getProduct()

    
    If (Application.CountIf(Sheets("ProizvodSheet").Columns(2), barcode) = False) Then
        MsgBox "Proizvod nije u bazi podataka!"
        Exit Sub
    End If
     
        
         
        tb_Naziv.Text = Proizvod.VLookup_Naziv(barcode)
        tb_Cena.Text = Proizvod.VLookup_Cena(barcode)
         
 
        
     With lbl_BARCODE
        .Font.Name = "CCode39"
        .Font.Size = 13
        .Caption = "*" + tb_ScanBC.Text + "*"
     End With

End Sub



Private Sub tb_ScanBC_KeyPress(ByVal KeyAscii As MSForms.ReturnInteger)

    Dim i As Integer
    
    lb_AutoComplite.Clear
    
    lb_AutoComplite.Visible = True
    
    For i = 2 To Sheet2.Range("B1000").End(xlUp).row
        If UCase(Left(Sheet2.Cells(i, 2), Len(tb_ScanBC.Text))) = UCase(tb_ScanBC.Text) Then
            lb_AutoComplite.AddItem Sheet2.Cells(i, 2)
        End If
   Next i
    
End Sub


Private Sub lbl_PrintBarcode_Click()

      
    Proizvod.SheetTemplateBarkod = "BarkodTemplate"
    Proizvod.barkod = barcode
    Proizvod.Naziv = tb_Naziv.Text
    Proizvod.Cena = tb_Cena.Text
 

    Proizvod.StampajProizvod
 
   
End Sub

Private Sub lb_AutoComplite_Click()
    tb_ScanBC.Text = lb_AutoComplite.value
    lb_AutoComplite.Visible = False
End Sub

 Private Sub tb_ScanBC_Change()

    If tb_ScanBC.Text = "" Then
        lb_AutoComplite.Visible = False
    End If

End Sub



Private Sub lbl_Exit_Click()
    Unload Me
End Sub




' ==============================================================================
'                                   GUI
' ==============================================================================

Sub GUI()
    mouse_down = False
    
    frm_ADD.Height = 280

    blue01_Color = RGB(22, 144, 248)
    grey01_Color = RGB(171, 171, 171)
    btn_Color = RGB(50, 52, 77)
    white_Color = RGB(239, 238, 230)
    hoverDark_Color = RGB(103, 103, 105)
    
    Me.BackColor = grey01_Color
    
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    lbl_TopBar.BackColor = btn_Color
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
    lbl_PrintBarcode.BackColor = btn_Color
    lbl_PrintBarcode_Out.BackColor = btn_Color
    
    Label01.BackColor = blue01_Color
    Label02.BackColor = blue01_Color
    Label03.BackColor = blue01_Color
  
End Sub




Private Sub lbl_Exit_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = white_Color
    lbl_Exit.ForeColor = btn_Color
End Sub


Private Sub lbl_TopBar_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    ' Form Move
    If mouse_down = True Then
        frm_PRINT_BC.Left = frm_PRINT_BC.Left + (X - mouse_starting_X)
        frm_PRINT_BC.Top = frm_PRINT_BC.Top + (Y - mouse_starting_Y)
    End If
End Sub



 
Private Sub lbl_PrintBarcode_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = hoverDark_Color

End Sub
Private Sub lbl_PrintBarcode_Out_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
End Sub

 
Private Sub UserForm_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    ' Label X
    lbl_Exit.BackColor = btn_Color
    lbl_Exit.ForeColor = white_Color
    
    ' Dugme PRINT
    lbl_PrintBarcode.ForeColor = white_Color
 
    
End Sub




'---------------------------------------------------------------------------------

Private Sub lbl_TopBar_MouseDown(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    mouse_down = True
    mouse_starting_X = X
    mouse_starting_Y = Y
End Sub


Private Sub lbl_TopBar_MouseUp(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
    mouse_down = False
End Sub


Početna Strana – Meni

Module “Meni”. Vezujemo dugmad sa menija sa našim makrom.

Public Sub run_Add()
    frm_ADD.Show
End Sub

Public Sub run_MAin()
    frm_MAIN.Show
End Sub

Public Sub run_PrintLabel()
    frm_PRINT_BC.Show
End Sub

Public Sub run_SheetProduct()
    Sheets("ProizvodSheet").Activate
End Sub

Public Sub run_Support()
     frm_support.Show
End Sub

Primer Barkod Tikete

Primer Izdatog Računa

Excel dokument iz ovog videa možete preuzeti na linku ispod.

Leave a Comment

Your email address will not be published. Required fields are marked *

Scroll to Top