Results 1 to 35 of 35

Thread: Image feature recognition algorithm

  1. #1

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Image feature recognition algorithm

    I am using scrcpy to synchronize the screen of my old Android phone to the computer device. This way I can monitor my phone screen on the computer. Everyone knows that scrcpy can set the screen compression in order to transmit the screen smoothly. Now I need to automatically recognize some "Signature marker" on the screen, and then get the notification...

    For example: I have an app on my old mobile phone. When the app gets the alarm message, it can pop up a specific image. I want to compare the image to identify whether the message has been received. I found a lot of color contrast methods in the forum. For example, the replacement color code by dilettante, this can be obtained if the appropriate tolerance is set. Of course, the success rate depends on the difference between the pattern and the background color.
    It's like identifying an apple in a picture. The color of this apple may be slightly different every time. This is because the screen of the mobile phone is compressed during the scrcpy transmission process.
    Attached Files Attached Files
    Last edited by xxdoc123; Dec 9th, 2021 at 10:01 PM.

  2. #2

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    The image captured by each screenshot may have slight differences in color, saturation, lightness and darkness

  3. #3

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    i post a demo.but is so slow

    Code:
    VERSION 5.00
    Begin VB.Form Form1 
       Caption         =   "Form1"
       ClientHeight    =   6168
       ClientLeft      =   108
       ClientTop       =   456
       ClientWidth     =   10128
       BeginProperty Font 
          Name            =   "Tahoma"
          Size            =   7.8
          Charset         =   0
          Weight          =   400
          Underline       =   0   'False
          Italic          =   0   'False
          Strikethrough   =   0   'False
       EndProperty
       LinkTopic       =   "Form1"
       ScaleHeight     =   514
       ScaleMode       =   3  'Pixel
       ScaleWidth      =   844
       ShowInTaskbar   =   0   'False
       StartUpPosition =   3  '窗口缺省
       Begin VB.PictureBox Picture3 
          AutoSize        =   -1  'True
          Height          =   4212
          Left            =   3960
          ScaleHeight     =   4164
          ScaleWidth      =   4848
          TabIndex        =   3
          TabStop         =   0   'False
          Top             =   1440
          Width           =   4896
       End
       Begin VB.CommandButton Command1 
          Caption         =   "Command1"
          Height          =   360
          Left            =   4560
          TabIndex        =   2
          Top             =   0
          Width           =   990
       End
       Begin VB.PictureBox Picture2 
          AutoSize        =   -1  'True
          Height          =   684
          Left            =   6000
          Picture         =   "Form1.frx":0000
          ScaleHeight     =   636
          ScaleWidth      =   780
          TabIndex        =   1
          TabStop         =   0   'False
          Top             =   720
          Width           =   828
       End
       Begin VB.PictureBox Picture1 
          AutoSize        =   -1  'True
          Height          =   2316
          Left            =   120
          Picture         =   "Form1.frx":28D6
          ScaleHeight     =   2268
          ScaleWidth      =   2952
          TabIndex        =   0
          TabStop         =   0   'False
          Top             =   240
          Width           =   3000
       End
    End
    Attribute VB_Name = "Form1"
    Attribute VB_GlobalNameSpace = False
    Attribute VB_Creatable = False
    Attribute VB_PredeclaredId = True
    Attribute VB_Exposed = False
    Option Explicit
    
    Private Sub Command1_Click()
        Picture1.ScaleMode = 3
        Picture1.AutoRedraw = True
        Picture1.AutoSize = True
        Picture2.ScaleMode = 3
        Picture2.AutoRedraw = True
        Picture2.AutoSize = True
        Picture3.Width = Picture1.Width
        Picture3.Height = Picture1.Height
        Picture3.AutoRedraw = True
        Picture3.AutoSize = True
        If Picture2.ScaleWidth > Picture1.ScaleWidth Or Picture2.ScaleHeight > Picture1.ScaleHeight Then
            MsgBox "The image size does not meet the requirements"
            Exit Sub
        End If
    
        Command1.Enabled = False
        Call ReadPic(Picture1.Image, iDATA())
        Call ReadPic(Picture2.Image, bDATA())
        Call TemplateMatchDib(Picture1.ScaleWidth, Picture1.ScaleHeight, Picture2.ScaleHeight, Picture2.ScaleWidth)
        Command1.Enabled = True
        Call ShowPic(Picture3.Image, iDATA)
    End Sub
    Code:
    Attribute VB_Name = "Module1"
    Option Explicit
    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
    Private Declare Function GetDIBits _
                    Lib "gdi32" (ByVal aHDC As Long, _
                                 ByVal hBitmap As Long, _
                                 ByVal nStartScan As Long, _
                                 ByVal nNumScans As Long, _
                                 lpBits As Any, _
                                 lpBI As BITMAPINFO, _
                                 ByVal wUsage As Long) As Long
    Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
    Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
    Private Declare Function SelectObject _
                    Lib "gdi32" (ByVal hdc As Long, _
                                 ByVal hObject As Long) As Long
    Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
    Private Declare Function GetObject _
                    Lib "gdi32" _
                    Alias "GetObjectA" (ByVal hObject As Long, _
                                        ByVal nCount As Long, _
                                        lpObject As Any) As Long
    Private Declare Function SetDIBits _
                    Lib "gdi32" (ByVal hdc As Long, _
                                 ByVal hBitmap As Long, _
                                 ByVal nStartScan As Long, _
                                 ByVal nNumScans As Long, _
                                 lpBits As Any, _
                                 lpBI As BITMAPINFO, _
                                 ByVal wUsage As Long) As Long
    Private Declare Sub CopyMemory _
                    Lib "kernel32" _
                    Alias "RtlMoveMemory" (pDst As Any, _
                                           pSrc As Any, _
                                           ByVal ByteLen As Long)
    Public Const SRCCOPY = &HCC0020
    
    Private Type BITMAP
        bmType As Long
        bmWidth As Long
        bmHeight As Long
        bmWidthBytes As Long
        bmPlanes As Integer
        bmBitsPixel As Integer
        bmBits As Long
    End Type
    
    Type BITMAPINFOHEADER '40 bytes
        biSize As Long 'BITMAPINFOHEADER
        biWidth As Long
        biHeight As Long
        biPlanes As Integer '
        biBitCount As Integer '
        biCompression As Long '
        biSizeImage As Long '
        biXPelsPerMeter As Long '
        biYPelsPerMeter As Long '
        biClrUsed As Long '
        biClrImportant As Long '
    End Type
    
    Type RGBQUAD '
        rgbBlue As Byte '
        rgbGreen As Byte '
        rgbRed As Byte '
        rgbReserved As Byte '
    End Type
    
    Type BITMAPINFO
        bmiHeader As BITMAPINFOHEADER
        bmiColors As RGBQUAD
    End Type
    
    Private Const BI_RGB = 0&
    Private Const DIB_RGB_COLORS = 0&
    Private Const LR_LOADFROMFILE = &H10
    Private Const IMAGE_BITMAP = 0&
    Private PicInfo As BITMAP '
    Private DIBInfo As BITMAPINFO 'Device Ind. Bitmap info structure
    Public iDATA()  As Byte
    Public bDATA()  As Byte '
    
    Public Sub ReadPic(ByVal pic As Long, data() As Byte) '
        Dim hdcNew              As Long
        Dim oldhand             As Long
        Dim ret                 As Long
        Dim BytesPerScanLine    As Long '
        Dim PadBytesPerScanLine As Long
        Call GetObject(pic, Len(PicInfo), PicInfo) '
        hdcNew = CreateCompatibleDC(0&) '
        oldhand = SelectObject(hdcNew, pic)
    
        With DIBInfo.bmiHeader
            .biSize = 40 '
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight '
            .biPlanes = 1
            .biBitCount = 32 '
            .biCompression = BI_RGB '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4) '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
            .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        ReDim data(1 To 4, 1 To PicInfo.bmWidth, 1 To PicInfo.bmHeight) As Byte
        ret = GetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    End Sub
    
    Public Sub ShowPic(ByVal pic As Long, data() As Byte) '
        Dim hdcNew              As Long
        Dim oldhand             As Long
        Dim ret                 As Long
        Dim BytesPerScanLine    As Long '
        Dim PadBytesPerScanLine As Long
        Call GetObject(pic, Len(PicInfo), PicInfo) '
        hdcNew = CreateCompatibleDC(0&) '
        oldhand = SelectObject(hdcNew, pic)
    
        With DIBInfo.bmiHeader
            .biSize = 40 'bmp3.0
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight '
            .biPlanes = 1
            .biBitCount = 32 '
            .biCompression = BI_RGB '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4) '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
           ' .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        ret = SetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    
        Form1.Picture3.Refresh
    End Sub
    
    
    Public Sub TemplateMatchDib(Lwidth As Long, Lheight As Long, Temph As Long, Tempw As Long)
        Dim i           As Integer, j As Integer, m As Integer, N As Integer
        Dim dsigmast    As Double, dsigmas As Double, dsigmat As Double, r As Double, maxr As Double
        Dim LmaxWidth   As Long, LmaxHeight As Long
        Dim MidMatrix() As Long
        ReDim MidMatrix(3, Lwidth, Lheight) As Long
    
        On Error Resume Next
    
        For i = 1 To Lwidth
            For j = 1 To Lheight
                For m = 1 To 3 '
                    MidMatrix(m, i, j) = 0 '
                Next m
            Next j
        Next i
    
        dsigmat = 0
    
        For N = 1 To Temph - 1
            For m = 1 To Tempw - 1
                dsigmat = dsigmat + Val(bDATA(1, m, N)) ^ 2
            Next m
        Next N
    
        maxr = 0
    
        For j = 1 To Lheight - Temph + 1 Step 1 '
            For i = 1 To Lwidth - Tempw + 1 Step 1 '
                dsigmast = 0
                dsigmas = 0 '
    
                For N = 1 To Temph
                    For m = 1 To Tempw
                        dsigmas = dsigmas + (Val(iDATA(1, i + m - 1, j + N - 1)) + Val(iDATA(2, i + m - 1, j + N - 1)) + Val(iDATA(3, i + m - 1, j + N - 1)) / 3) ^ 2
                        dsigmast = dsigmast + (Val(iDATA(1, i + m - 1, j + N - 1)) + Val(iDATA(2, i + m - 1, j + N - 1)) + Val(iDATA(3, i + m - 1, j + N - 1)) / 3) * (Val(bDATA(1, m, N)) + Val(bDATA(1, m, N)) + Val(bDATA(1, m, N))) / 3
    
                        DoEvents
                    Next m
                Next N
    
                r = dsigmast / (FASTsqr(dsigmas) * Sqr(dsigmat)) '
    
                If r > maxr Then '
                    maxr = r
                    LmaxWidth = i
                    LmaxHeight = j
                    Debug.Print r
                     If r > 1 Then ' 1 may  or  oher.
                    
                    Form1.Picture1.Line (LmaxWidth, LmaxHeight)-(LmaxWidth + Tempw, LmaxHeight + Temph), vbRed, B
                    
                     GoTo h:
                    
                     End If
                End If
    
                DoEvents
            Next i
    
            DoEvents
        Next j
    h:
        For N = 1 To Temph '
            For m = 1 To Tempw
                MidMatrix(1, m + LmaxWidth, N + LmaxHeight) = bDATA(1, m, N)
                MidMatrix(2, m + LmaxWidth, N + LmaxHeight) = bDATA(2, m, N)
                MidMatrix(3, m + LmaxWidth, N + LmaxHeight) = bDATA(3, m, N)
            Next m
        Next N
    
        For i = 1 To Lwidth
            For j = 1 To Lheight
                For m = 1 To 3
                    iDATA(m, i, j) = MidMatrix(m, i, j)
                Next m
            Next j
        Next i
    
    End Sub
    
    
    Public Function FASTsqr(N As Double) As Double
        Dim X      As Double
        Dim ox     As Double
    
        If N Then
            X = N * 0.5
            Do
                ox = X
                X = (X + (N / X)) * 0.5
            Loop While ox <> X
    
            FASTsqr = X
    
        End If
        
      
    
    End Function
    Last edited by xxdoc123; Dec 4th, 2021 at 11:53 PM.

  4. #4
    Fanatic Member
    Join Date
    Sep 2010
    Location
    Italy
    Posts
    678

    Re: Image feature recognition algorithm

    Code:
    Private Sub Command1_Click()
        Picture1.ScaleMode = 3
        Picture1.AutoRedraw = True
        Picture1.AutoSize = True
    
        Picture2.ScaleMode = 3
        Picture2.AutoRedraw = True
        Picture2.AutoSize = True
    
        Picture3.ScaleMode = 3
        Picture3.Width = Picture1.Width
        Picture3.Height = Picture1.Height
        Picture3.AutoRedraw = True
        Picture3.AutoSize = True
        If Picture2.ScaleWidth > Picture1.ScaleWidth Or Picture2.ScaleHeight > Picture1.ScaleHeight Then
            MsgBox "The image size does not meet the requirements"
            Exit Sub
        End If
    
        Command1.Enabled = False
        Call ReadPic(Picture1.Image, iDATA())
        Call ReadPic(Picture2.Image, bDATA())
    
    
        ' Call TemplateMatchDib(Picture1.ScaleWidth, Picture1.ScaleHeight, Picture2.ScaleHeight, Picture2.ScaleWidth)
    
        Call FOUND(iDATA(), bDATA())
    
        Command1.Enabled = True
        Call ShowPic(Picture3.Image, iDATA)
    End Sub
    Code:
    Public Sub ReadPic(ByVal PIC As Long, Data() As Byte)    '
        Dim hdcNew     As Long
        Dim oldhand    As Long
        Dim ret        As Long
        Dim BytesPerScanLine As Long    '
        Dim PadBytesPerScanLine As Long
        Call GetObject(PIC, Len(PicInfo), PicInfo)    '
        hdcNew = CreateCompatibleDC(0&)    '
        oldhand = SelectObject(hdcNew, PIC)
    
        With DIBInfo.bmiHeader
            .biSize = 40    '
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight    '
            .biPlanes = 1
            .biBitCount = 32    '
            .biCompression = BI_RGB    '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4)    '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
            .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        'ReDim data(1 To 4, 1 To PicInfo.bmWidth, 1 To PicInfo.bmHeight) As Byte
        ReDim Data(0 To 3, 0 To PicInfo.bmWidth - 1, 0 To PicInfo.bmHeight - 1) As Byte
    
        '    ret = GetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        ret = GetDIBits(hdcNew, PIC, 0, PicInfo.bmHeight, Data(0, 0, 0), DIBInfo, DIB_RGB_COLORS)
    
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    End Sub
    
    Public Sub ShowPic(ByVal PIC As Long, Data() As Byte)    '
        Dim hdcNew     As Long
        Dim oldhand    As Long
        Dim ret        As Long
        Dim BytesPerScanLine As Long    '
        Dim PadBytesPerScanLine As Long
        Call GetObject(PIC, Len(PicInfo), PicInfo)    '
        hdcNew = CreateCompatibleDC(0&)    '
        oldhand = SelectObject(hdcNew, PIC)
    
        With DIBInfo.bmiHeader
            .biSize = 40    'bmp3.0
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight    '
            .biPlanes = 1
            .biBitCount = 32    '
            .biCompression = BI_RGB    '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4)    '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
            .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        'ret = SetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        ret = SetDIBits(hdcNew, PIC, 0, PicInfo.bmHeight, Data(0, 0, 0), DIBInfo, DIB_RGB_COLORS)
    
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    
      
    End Sub
    Code:
    Public Sub FOUND(Source() As Byte, toFind() As Byte)
        ' COMPILE with all optimization ON.  [but alias?]
    
        Dim X&, Y&
        Dim W&, H&
        Dim X2&, Y2&
        Dim W2&, H2&
    
        Dim pDR        As Double    'Pixel Delta
        Dim pDG        As Double
        Dim pDB        As Double
    
        Dim tDR        As Double    'Total Pixel Delta
        Dim tDG        As Double
        Dim tDB        As Double
    
        Dim Result()   As Double
        Dim MinR       As Double
        Dim MaxR       As Double
    
        W = UBound(Source, 2)
        H = UBound(Source, 3)
        W2 = UBound(toFind, 2)
        H2 = UBound(toFind, 3)
    
        ReDim Result(W, H)
    
        For X = 0 To W - W2 Step 1    'To Speed up You can play with Step
            For Y = 0 To H - H2 Step 1
                tDR = 0
                tDG = 0
                tDB = 0
                For X2 = 0 To W2 Step 4    'To Speed up You can play with Step
                    For Y2 = 0 To H2 Step 4
                        pDR = Source(2, X + X2, Y + Y2) * 1 - toFind(2, X2, Y2) * 1
                        pDG = Source(1, X + X2, Y + Y2) * 1 - toFind(1, X2, Y2) * 1
                        pDB = Source(0, X + X2, Y + Y2) * 1 - toFind(0, X2, Y2) * 1
                        tDR = tDR + pDR * pDR
                        tDG = tDG + pDG * pDG
                        tDB = tDB + pDB * pDB
                    Next
                Next
                Result(X, Y) = tDR + tDG + tDB
                If Result(X, Y) > MaxR Then MaxR = Result(X, Y)
    
            Next
        Next
        
        MaxR = 255 / MaxR
        MinR = 1E+32
        For X = 0 To W - W2
            For Y = 0 To H - H2
                If Result(X, Y) Then
                    If (Result(X, Y) < MinR) Then
                        MinR = Result(X, Y)
                        X2 = X
                        Y2 = Y
                    End If
                End If
                Source(2, X, Y) = Result(X, Y) * MaxR
                Source(1, X, Y) = Result(X, Y) * MaxR
                Source(0, X, Y) = Result(X, Y) * MaxR
            Next
        Next
    
        For X = 0 To W2
            For Y = 0 To H2
                Source(2, X2 + X, Y2 + Y) = toFind(2, X, Y)
                Source(1, X2 + X, Y2 + Y) = toFind(1, X, Y)
                Source(0, X2 + X, Y2 + Y) = toFind(0, X, Y)
            Next
        Next
    
    End Sub

  5. #5
    PowerPoster
    Join Date
    Feb 2017
    Posts
    5,067

    Re: Image feature recognition algorithm

    If you know in which sector of the screen the sub image that serves as the marker will appear, you could test for a couple of pixels to see if the colors match. In your example it would be easy, since you don't have red or magenta in the rest of the image.

  6. #6

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by reexre View Post
    Code:
    Private Sub Command1_Click()
        Picture1.ScaleMode = 3
        Picture1.AutoRedraw = True
        Picture1.AutoSize = True
    
        Picture2.ScaleMode = 3
        Picture2.AutoRedraw = True
        Picture2.AutoSize = True
    
        Picture3.ScaleMode = 3
        Picture3.Width = Picture1.Width
        Picture3.Height = Picture1.Height
        Picture3.AutoRedraw = True
        Picture3.AutoSize = True
        If Picture2.ScaleWidth > Picture1.ScaleWidth Or Picture2.ScaleHeight > Picture1.ScaleHeight Then
            MsgBox "The image size does not meet the requirements"
            Exit Sub
        End If
    
        Command1.Enabled = False
        Call ReadPic(Picture1.Image, iDATA())
        Call ReadPic(Picture2.Image, bDATA())
    
    
        ' Call TemplateMatchDib(Picture1.ScaleWidth, Picture1.ScaleHeight, Picture2.ScaleHeight, Picture2.ScaleWidth)
    
        Call FOUND(iDATA(), bDATA())
    
        Command1.Enabled = True
        Call ShowPic(Picture3.Image, iDATA)
    End Sub
    Code:
    Public Sub ReadPic(ByVal PIC As Long, Data() As Byte)    '
        Dim hdcNew     As Long
        Dim oldhand    As Long
        Dim ret        As Long
        Dim BytesPerScanLine As Long    '
        Dim PadBytesPerScanLine As Long
        Call GetObject(PIC, Len(PicInfo), PicInfo)    '
        hdcNew = CreateCompatibleDC(0&)    '
        oldhand = SelectObject(hdcNew, PIC)
    
        With DIBInfo.bmiHeader
            .biSize = 40    '
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight    '
            .biPlanes = 1
            .biBitCount = 32    '
            .biCompression = BI_RGB    '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4)    '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
            .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        'ReDim data(1 To 4, 1 To PicInfo.bmWidth, 1 To PicInfo.bmHeight) As Byte
        ReDim Data(0 To 3, 0 To PicInfo.bmWidth - 1, 0 To PicInfo.bmHeight - 1) As Byte
    
        '    ret = GetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        ret = GetDIBits(hdcNew, PIC, 0, PicInfo.bmHeight, Data(0, 0, 0), DIBInfo, DIB_RGB_COLORS)
    
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    End Sub
    
    Public Sub ShowPic(ByVal PIC As Long, Data() As Byte)    '
        Dim hdcNew     As Long
        Dim oldhand    As Long
        Dim ret        As Long
        Dim BytesPerScanLine As Long    '
        Dim PadBytesPerScanLine As Long
        Call GetObject(PIC, Len(PicInfo), PicInfo)    '
        hdcNew = CreateCompatibleDC(0&)    '
        oldhand = SelectObject(hdcNew, PIC)
    
        With DIBInfo.bmiHeader
            .biSize = 40    'bmp3.0
            .biWidth = PicInfo.bmWidth
            .biHeight = -PicInfo.bmHeight    '
            .biPlanes = 1
            .biBitCount = 32    '
            .biCompression = BI_RGB    '
            BytesPerScanLine = ((((.biWidth * .biBitCount) + 31) \ 32) * 4)    '
            PadBytesPerScanLine = BytesPerScanLine - (((.biWidth * .biBitCount) + 7) \ 8)
            .biSizeImage = BytesPerScanLine * Abs(.biHeight)
        End With
    
        'ret = SetDIBits(hdcNew, pic, 0, PicInfo.bmHeight, data(1, 1, 1), DIBInfo, DIB_RGB_COLORS)
        ret = SetDIBits(hdcNew, PIC, 0, PicInfo.bmHeight, Data(0, 0, 0), DIBInfo, DIB_RGB_COLORS)
    
        SelectObject hdcNew, oldhand
        DeleteDC hdcNew
    
      
    End Sub
    Code:
    Public Sub FOUND(Source() As Byte, toFind() As Byte)
        ' COMPILE with all optimization ON.  [but alias?]
    
        Dim X&, Y&
        Dim W&, H&
        Dim X2&, Y2&
        Dim W2&, H2&
    
        Dim pDR        As Double    'Pixel Delta
        Dim pDG        As Double
        Dim pDB        As Double
    
        Dim tDR        As Double    'Total Pixel Delta
        Dim tDG        As Double
        Dim tDB        As Double
    
        Dim Result()   As Double
        Dim MinR       As Double
        Dim MaxR       As Double
    
        W = UBound(Source, 2)
        H = UBound(Source, 3)
        W2 = UBound(toFind, 2)
        H2 = UBound(toFind, 3)
    
        ReDim Result(W, H)
    
        For X = 0 To W - W2 Step 1    'To Speed up You can play with Step
            For Y = 0 To H - H2 Step 1
                tDR = 0
                tDG = 0
                tDB = 0
                For X2 = 0 To W2 Step 4    'To Speed up You can play with Step
                    For Y2 = 0 To H2 Step 4
                        pDR = Source(2, X + X2, Y + Y2) * 1 - toFind(2, X2, Y2) * 1
                        pDG = Source(1, X + X2, Y + Y2) * 1 - toFind(1, X2, Y2) * 1
                        pDB = Source(0, X + X2, Y + Y2) * 1 - toFind(0, X2, Y2) * 1
                        tDR = tDR + pDR * pDR
                        tDG = tDG + pDG * pDG
                        tDB = tDB + pDB * pDB
                    Next
                Next
                Result(X, Y) = tDR + tDG + tDB
                If Result(X, Y) > MaxR Then MaxR = Result(X, Y)
    
            Next
        Next
        
        MaxR = 255 / MaxR
        MinR = 1E+32
        For X = 0 To W - W2
            For Y = 0 To H - H2
                If Result(X, Y) Then
                    If (Result(X, Y) < MinR) Then
                        MinR = Result(X, Y)
                        X2 = X
                        Y2 = Y
                    End If
                End If
                Source(2, X, Y) = Result(X, Y) * MaxR
                Source(1, X, Y) = Result(X, Y) * MaxR
                Source(0, X, Y) = Result(X, Y) * MaxR
            Next
        Next
    
        For X = 0 To W2
            For Y = 0 To H2
                Source(2, X2 + X, Y2 + Y) = toFind(2, X, Y)
                Source(1, X2 + X, Y2 + Y) = toFind(1, X, Y)
                Source(0, X2 + X, Y2 + Y) = toFind(0, X, Y)
            Next
        Next
    
    End Sub
    Your code looks more standardized.However, this method of overall comparison of chromatic aberrations still has certain flaws. Visually completely different images will appear the same difference.


    Code:
        For X = 0 To W - W2 Step 1    'To Speed up You can play with Step
            For Y = 0 To H - H2 Step 1
                tDR = 0
                tDG = 0
                tDB = 0
                For X2 = 0 To W2 Step 4    'To Speed up You can play with Step
                    For Y2 = 0 To H2 Step 4
                        pDR = Source(2, X + X2, Y + Y2) * 1 - toFind(2, X2, Y2) * 1
                        pDG = Source(1, X + X2, Y + Y2) * 1 - toFind(1, X2, Y2) * 1
                        pDB = Source(0, X + X2, Y + Y2) * 1 - toFind(0, X2, Y2) * 1
                       if abs(pDR )<50 and  abs(pDG )<50  and abs(pDB )<50 then ' 50 is Color difference'
                             sameNum =sameNum+1
                       end if
    
    
                    Next
                Next
                if sameNum >W2*H2* 0.9 then '0.9 is Similarity ratio
                   msgbox "find" 
                
                  sameNum =0
                end if
    
            Next
        Next

  7. #7

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by Eduardo- View Post
    If you know in which sector of the screen the sub image that serves as the marker will appear, you could test for a couple of pixels to see if the colors match. In your example it would be easy, since you don't have red or magenta in the rest of the image.
    you are right. If the color difference between the target and the background is obvious, the color finding is indeed faster and accurate.

    I don’t know if there is an algorithm for image contour comparison. In this way, through grayscale, binarization, and contour comparison, you can ignore the difference in color. It seems that this is a bit more difficult. And if the target image is not the same size as the template image

  8. #8
    PowerPoster
    Join Date
    Feb 2017
    Posts
    5,067

    Re: Image feature recognition algorithm

    Inspired by your question I started to work in am image comparison tool (that BTW it is already more or less working).
    But reading again your OP and being downloaded your sample images, I realize that an Image comparison tool like the one I'm doing won't serve for what you want.
    You need to recognize a small image into a larger one, and that's not what my current project does.

    For what you need, if you know the place where the smaller image will be, it could be quite easy to check whether it is there or not.
    As I said, I would just check for a couple of pixels.

  9. #9

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by Eduardo- View Post
    Inspired by your question I started to work in am image comparison tool (that BTW it is already more or less working).
    But reading again your OP and being downloaded your sample images, I realize that an Image comparison tool like the one I'm doing won't serve for what you want.
    You need to recognize a small image into a larger one, and that's not what my current project does.

    For what you need, if you know the place where the smaller image will be, it could be quite easy to check whether it is there or not.
    As I said, I would just check for a couple of pixels.
    which your tool?

  10. #10
    PowerPoster
    Join Date
    Feb 2017
    Posts
    5,067

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    which your tool?
    I do not understand the question.

  11. #11

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by Eduardo- View Post
    I do not understand the question.
    image comparison tool

  12. #12
    Fanatic Member
    Join Date
    Sep 2010
    Location
    Italy
    Posts
    678

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    ... However, this method of overall comparison of chromatic aberrations still has certain flaws. Visually completely different images will appear the same difference.
    I'm not so convinced about that.
    However, I was inspired to try to calculate the result based on the edges.
    I tried using just their magnitudes but it didn't seem to work well. (perhaps for similar reasons to what you were saying).
    So I added the orientation of the edges.
    This seems to work fine.
    I haven't done much testing though.

    Code:
    Public Const PI   As Double = 3.14159265358979
    Public Const PIh  As Double = 1.5707963267949
    Public Const PI2  As Double = 6.28318530717959
    
    Private Function Atan2(X As Double, Y As Double) As Double
        If X Then
            Atan2 = -PI + Atn(Y / X) - (X > 0#) * PI
        Else
            Atan2 = -PIh - (Y > 0#) * PI
        End If
    End Function
    Private Function AngleDIFF(A1 As Double, A2 As Double) As Double
        AngleDIFF = A1 - A2
        While AngleDIFF < -PI
            AngleDIFF = AngleDIFF + PI2
        Wend
        While AngleDIFF > PI
            AngleDIFF = AngleDIFF - PI2
        Wend
    End Function
    Public Sub FOUND2(Source() As Byte, toFind() As Byte)
        Dim X&, Y&
        Dim W&, H&
        Dim X2&, Y2&
        Dim W2&, H2&
    
        Dim pDR       As Double
        Dim pDG       As Double
        Dim pDB       As Double
        Dim tDR       As Double
        Dim tDG       As Double
        Dim tDB       As Double
    
        Dim Result()  As Double
        Dim EdgeAng1() As Double
        Dim EdgeAng2() As Double
        Dim MAG2()    As Double
        Dim MAG1()    As Double
    
        Dim DX#, DY#
        Dim MinR      As Double
        Dim MaxR      As Double
    
        W = UBound(Source, 2)
        H = UBound(Source, 3)
        W2 = UBound(toFind, 2)
        H2 = UBound(toFind, 3)
    
        ReDim Result(W, H)
        ReDim EdgeAng1(W, H)
        ReDim EdgeAng2(W2, H2)
        ReDim MAG1(W, H)
        ReDim MAG2(W2, H2)                           'EDGE magnitude
    
        ' Convert to Edge Angle --------------------------
        For Y = 1 To H - 1
            For X = 1 To W - 1
                pDR = Source(2, X - 1, Y) * 1 - Source(2, X + 1, Y) * 1
                pDG = Source(1, X - 1, Y) * 1 - Source(1, X + 1, Y) * 1
                pDB = Source(0, X - 1, Y) * 1 - Source(0, X + 1, Y) * 1
                DX = (pDR) + (pDG) + (pDB)
                pDR = Source(2, X, Y - 1) * 1 - Source(2, X, Y + 1) * 1
                pDG = Source(1, X, Y - 1) * 1 - Source(1, X, Y + 1) * 1
                pDB = Source(0, X, Y - 1) * 1 - Source(0, X, Y + 1) * 1
                DY = (pDR) + (pDG) + (pDB)
                EdgeAng1(X, Y) = Atan2(DX, DY)
                MAG1(X, Y) = Sqr(DX * DX + DY * DY)
            Next
        Next
        For Y = 1 To H2 - 1
            For X = 1 To W2 - 1
                pDR = toFind(2, X - 1, Y) * 1 - toFind(2, X + 1, Y) * 1
                pDG = toFind(1, X - 1, Y) * 1 - toFind(1, X + 1, Y) * 1
                pDB = toFind(0, X - 1, Y) * 1 - toFind(0, X + 1, Y) * 1
                DX = (pDR) + (pDG) + (pDB)
                pDR = toFind(2, X, Y - 1) * 1 - toFind(2, X, Y + 1) * 1
                pDG = toFind(1, X, Y - 1) * 1 - toFind(1, X, Y + 1) * 1
                pDB = toFind(0, X, Y - 1) * 1 - toFind(0, X, Y + 1) * 1
                DY = (pDR) + (pDG) + (pDB)
                EdgeAng2(X, Y) = Atan2(DX, DY)
                MAG2(X, Y) = Sqr(DX * DX + DY * DY)
            Next
        Next
        '---------------------------------
    
        For X = 0 To W - W2
            For Y = 0 To H - H2
                tDR = 0
                For X2 = 0 To W2 Step 4
                    For Y2 = 0 To H2 Step 4
                        pDR = AngleDIFF(EdgeAng1(X + X2, Y + Y2), EdgeAng2(X2, Y2))
                        tDR = tDR + pDR * pDR  * MAG2(X2, Y2)
                    Next
                Next
                Result(X, Y) = tDR
                If Result(X, Y) > MaxR Then MaxR = Result(X, Y)
            Next
        Next
    
        MaxR = 255 / MaxR
        MinR = 1E+32
        For X = 0 To W - W2
            For Y = 0 To H - H2
                If Result(X, Y) Then
                    If (Result(X, Y) < MinR) Then
                        MinR = Result(X, Y)
                        X2 = X
                        Y2 = Y
                    End If
                End If
                Source(2, X, Y) = Result(X, Y) * MaxR
                Source(1, X, Y) = Result(X, Y) * MaxR
                Source(0, X, Y) = Result(X, Y) * MaxR
            Next
        Next
    
        For X = 0 To W2
            For Y = 0 To H2
                Source(2, X2 + X, Y2 + Y) = toFind(2, X, Y)
                Source(1, X2 + X, Y2 + Y) = toFind(1, X, Y)
                Source(0, X2 + X, Y2 + Y) = toFind(0, X, Y)
            Next
        Next
    End Sub
    EDIT
    Code:
                pDR = toFind(2, X, Y - 1) * 1 - toFind(2, X, Y + 1) * 1
                pDG = toFind(1, X, Y - 1) * 1 - toFind(1, X, Y + 1) * 1
                pDB = toFind(0, X, Y - 1) * 1 - toFind(0, X, Y + 1) * 1

  13. #13

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by reexre View Post
    I'm not so convinced about that.
    However, I was inspired to try to calculate the result based on the edges.
    I tried using just their magnitudes but it didn't seem to work well. (perhaps for similar reasons to what you were saying).
    So I added the orientation of the edges.
    This seems to work fine.
    I haven't done much testing though.

    Code:
    Public Const PI   As Double = 3.14159265358979
    Public Const PIh  As Double = 1.5707963267949
    Public Const PI2  As Double = 6.28318530717959
    
    Private Function Atan2(X As Double, Y As Double) As Double
        If X Then
            Atan2 = -PI + Atn(Y / X) - (X > 0#) * PI
        Else
            Atan2 = -PIh - (Y > 0#) * PI
        End If
    End Function
    Private Function AngleDIFF(A1 As Double, A2 As Double) As Double
        AngleDIFF = A1 - A2
        While AngleDIFF < -PI
            AngleDIFF = AngleDIFF + PI2
        Wend
        While AngleDIFF > PI
            AngleDIFF = AngleDIFF - PI2
        Wend
    End Function
    Public Sub FOUND2(Source() As Byte, toFind() As Byte)
        Dim X&, Y&
        Dim W&, H&
        Dim X2&, Y2&
        Dim W2&, H2&
    
        Dim pDR       As Double
        Dim pDG       As Double
        Dim pDB       As Double
        Dim tDR       As Double
        Dim tDG       As Double
        Dim tDB       As Double
    
        Dim Result()  As Double
        Dim EdgeAng1() As Double
        Dim EdgeAng2() As Double
        Dim MAG2()    As Double
        Dim MAG1()    As Double
    
        Dim DX#, DY#
        Dim MinR      As Double
        Dim MaxR      As Double
    
        W = UBound(Source, 2)
        H = UBound(Source, 3)
        W2 = UBound(toFind, 2)
        H2 = UBound(toFind, 3)
    
        ReDim Result(W, H)
        ReDim EdgeAng1(W, H)
        ReDim EdgeAng2(W2, H2)
        ReDim MAG1(W, H)
        ReDim MAG2(W2, H2)                           'EDGE magnitude
    
        ' Convert to Edge Angle --------------------------
        For Y = 1 To H - 1
            For X = 1 To W - 1
                pDR = Source(2, X - 1, Y) * 1 - Source(2, X + 1, Y) * 1
                pDG = Source(1, X - 1, Y) * 1 - Source(1, X + 1, Y) * 1
                pDB = Source(0, X - 1, Y) * 1 - Source(0, X + 1, Y) * 1
                DX = (pDR) + (pDG) + (pDB)
                pDR = Source(2, X, Y - 1) * 1 - Source(2, X, Y + 1) * 1
                pDG = Source(1, X, Y - 1) * 1 - Source(1, X, Y + 1) * 1
                pDB = Source(0, X, Y - 1) * 1 - Source(0, X, Y + 1) * 1
                DY = (pDR) + (pDG) + (pDB)
                EdgeAng1(X, Y) = Atan2(DX, DY)
                MAG1(X, Y) = Sqr(DX * DX + DY * DY)
            Next
        Next
        For Y = 1 To H2 - 1
            For X = 1 To W2 - 1
                pDR = toFind(2, X - 1, Y) * 1 - toFind(2, X + 1, Y) * 1
                pDG = toFind(1, X - 1, Y) * 1 - toFind(1, X + 1, Y) * 1
                pDB = toFind(0, X - 1, Y) * 1 - toFind(0, X + 1, Y) * 1
                DX = (pDR) + (pDG) + (pDB)
                pDR = toFind(2, X, Y - 1) * 1 - toFind(2, X, Y + 1) * 1
                pDG = toFind(1, X, Y - 1) * 1 - toFind(1, X, Y + 1) * 1
                pDB = toFind(0, X, Y - 1) * 1 - toFind(0, X, Y + 1) * 1
                DY = (pDR) + (pDG) + (pDB)
                EdgeAng2(X, Y) = Atan2(DX, DY)
                MAG2(X, Y) = Sqr(DX * DX + DY * DY)
            Next
        Next
        '---------------------------------
    
        For X = 0 To W - W2
            For Y = 0 To H - H2
                tDR = 0
                For X2 = 0 To W2 Step 4
                    For Y2 = 0 To H2 Step 4
                        pDR = AngleDIFF(EdgeAng1(X + X2, Y + Y2), EdgeAng2(X2, Y2))
                        tDR = tDR + pDR * pDR  * MAG2(X2, Y2)
                    Next
                Next
                Result(X, Y) = tDR
                If Result(X, Y) > MaxR Then MaxR = Result(X, Y)
            Next
        Next
    
        MaxR = 255 / MaxR
        MinR = 1E+32
        For X = 0 To W - W2
            For Y = 0 To H - H2
                If Result(X, Y) Then
                    If (Result(X, Y) < MinR) Then
                        MinR = Result(X, Y)
                        X2 = X
                        Y2 = Y
                    End If
                End If
                Source(2, X, Y) = Result(X, Y) * MaxR
                Source(1, X, Y) = Result(X, Y) * MaxR
                Source(0, X, Y) = Result(X, Y) * MaxR
            Next
        Next
    
        For X = 0 To W2
            For Y = 0 To H2
                Source(2, X2 + X, Y2 + Y) = toFind(2, X, Y)
                Source(1, X2 + X, Y2 + Y) = toFind(1, X, Y)
                Source(0, X2 + X, Y2 + Y) = toFind(0, X, Y)
            Next
        Next
    End Sub
    EDIT
    Code:
                pDR = toFind(2, X, Y - 1) * 1 - toFind(2, X, Y + 1) * 1
                pDG = toFind(1, X, Y - 1) * 1 - toFind(1, X, Y + 1) * 1
                pDB = toFind(0, X, Y - 1) * 1 - toFind(0, X, Y + 1) * 1
    The effect is good.i test binarization, grayscale and other matching can also be well supported

    pic search.zip


    Name:  test1.jpg
Views: 613
Size:  46.1 KB
    =========================================

    Name:  test2.jpg
Views: 607
Size:  39.3 KB

    =============================================

    Name:  test3.jpg
Views: 561
Size:  41.2 KB
    ====================================================


    Name:  test4.jpg
Views: 630
Size:  39.1 KB
    ===============================================

    Name:  test5.jpg
Views: 608
Size:  46.5 KB
    Last edited by xxdoc123; Dec 9th, 2021 at 10:03 PM.

  14. #14

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    i found this

    https://github.com/WallBreaker2/op

    Windows message simulation, common keyboard message and mouse message simulation.
    Support common screenshots, GDI, DX (including d3d9, D3D10, d3d11), OpenGL screenshots, and minimize screenshots of common simulators (lightning, night God)
    Find color and map, support color deviation and fuzzy recognition
    Character recognition (OCR) supports 255 x 255 large dot matrix at most, color deviation, fuzzy recognition, system font library and desert font library
    The plug-in has 32-bit and 64 bit versions and supports 32 / 64 bit binding
    The project is completely open source, no back door, no virus, and can be used safely

  15. #15

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Through the mask map, the feature image is obtained. In this way, the background can be ignored and the image can be found.Name:  pic.jpg
Views: 575
Size:  34.0 KB
    Last edited by xxdoc123; Dec 12th, 2021 at 09:43 PM.

  16. #16
    Lively Member
    Join Date
    Jan 2005
    Posts
    114

    Re: Image feature recognition algorithm

    I don’t know if there is an algorithm for image contour comparison.
    If you can convert the image to b/w and know its position on screen then you can use histogram to detect the image. I wrote a simple image recognition program using this technique working well to read playing cards captured by a camera.
    I sliced the area (not necessarily to scale) then saved number of black pixels in each rectangle. Then the black pixels in the same area of the captured image is counted, difference from the reference is squared and errors are added up. If it is below some value for a defined shape then that shape is decided.
    Attached picture is for 45 x 45 pixels apple, very randomly sliced just to give an idea. You can decide how to slice to get a better estimation. You can expect quite a difference between apple and pear .
    Name:  apple.png
Views: 568
Size:  829 Bytes

  17. #17

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by kiymik View Post
    If you can convert the image to b/w and know its position on screen then you can use histogram to detect the image. I wrote a simple image recognition program using this technique working well to read playing cards captured by a camera.
    I sliced the area (not necessarily to scale) then saved number of black pixels in each rectangle. Then the black pixels in the same area of the captured image is counted, difference from the reference is squared and errors are added up. If it is below some value for a defined shape then that shape is decided.
    Attached picture is for 45 x 45 pixels apple, very randomly sliced just to give an idea. You can decide how to slice to get a better estimation. You can expect quite a difference between apple and pear .
    Name:  apple.png
Views: 568
Size:  829 Bytes
    I searched a lot of algorithms. But many are not in vb language.

    use histogram to detect
    can you give a demo ?

  18. #18
    Lively Member
    Join Date
    Jan 2005
    Posts
    114

    Re: Image feature recognition algorithm

    I didn't write a vb program for it, wrote only assembler for microcontroller. But I will write the algorithm with two sample images, the club and heart of playing cards, resized to 48x64 pixels (heart is stretced so aspect ratio is not as original but it shouldn't be required for your project).
    The images are divided into 4 rows and 3 columns of 16x16 pixels each (background colored for indication). So each image has 12 histogram values, starting from upper left to right :
    Club : 21, 244, 17, 88, 208, 88, 250, 228, 250, 67, 76, 67 black pixels (not precisely counted).
    Heart : 224, 181, 224, 229, 256, 229, 122, 256, 122, 6, 172, 6 black pixels.
    You can read the pixel by Point instruction to count blacks in desired region (or any desired color if working with colors).
    Then calculate sum of squares of differences for each area. An example with a distorted club shape is also given.
    Distorted club : 40, 233, 7, 79, 198, 60, 256, 236, 251, 99, 105, 30 black pixels.
    Divergence from reference club : (21-40)^2+(244-233)^2+... = 4882
    Divergence from reference heart : (224-40)^2+(181-233)^2+... = 248761
    You will see a lot of difference, enough to decide the shape. I hope it gived an idea how you can detect an image.
    Name:  Heart-48x64.png
Views: 562
Size:  461 Bytes Name:  Club-48x64.png
Views: 551
Size:  475 Bytes Name:  Club-48x64-distorted.png
Views: 552
Size:  536 Bytes

  19. #19

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by kiymik View Post
    I didn't write a vb program for it, wrote only assembler for microcontroller. But I will write the algorithm with two sample images, the club and heart of playing cards, resized to 48x64 pixels (heart is stretced so aspect ratio is not as original but it shouldn't be required for your project).
    The images are divided into 4 rows and 3 columns of 16x16 pixels each (background colored for indication). So each image has 12 histogram values, starting from upper left to right :
    Club : 21, 244, 17, 88, 208, 88, 250, 228, 250, 67, 76, 67 black pixels (not precisely counted).
    Heart : 224, 181, 224, 229, 256, 229, 122, 256, 122, 6, 172, 6 black pixels.
    You can read the pixel by Point instruction to count blacks in desired region (or any desired color if working with colors).
    Then calculate sum of squares of differences for each area. An example with a distorted club shape is also given.
    Distorted club : 40, 233, 7, 79, 198, 60, 256, 236, 251, 99, 105, 30 black pixels.
    Divergence from reference club : (21-40)^2+(244-233)^2+... = 4882
    Divergence from reference heart : (224-40)^2+(181-233)^2+... = 248761
    You will see a lot of difference, enough to decide the shape. I hope it gived an idea how you can detect an image.
    Name:  Heart-48x64.png
Views: 562
Size:  461 Bytes Name:  Club-48x64.png
Views: 551
Size:  475 Bytes Name:  Club-48x64-distorted.png
Views: 552
Size:  536 Bytes
    may be euclidean metric?

  20. #20
    Lively Member
    Join Date
    Jan 2005
    Posts
    114

    Re: Image feature recognition algorithm

    Yes, it is so, if only global comparison will be done no need to calculate squareroot. Since I was writing for a limited memory (and speed) microcontroller I didn't use squareroot.

  21. #21

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by kiymik View Post
    Yes, it is so, if only global comparison will be done no need to calculate squareroot. Since I was writing for a limited memory (and speed) microcontroller I didn't use squareroot.
    Feel the speed will slow down

  22. #22

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    used Hamming to test

    Code:
    Public Sub FOUND3(Source() As Byte, toFind() As Byte)
        ' COMPILE with all optimization ON.  [but alias?]
    
        Dim X&, Y&
        Dim W&, H&
        Dim X2&, Y2&
        Dim W2&, H2&
        Dim X3&, Y3&
    
        Dim pDR      As Double    'Pixel Delta
        Dim pDG      As Double
        Dim pDB      As Double
    
        Dim tDR      As Double    'Total Pixel Delta
        Dim tDG      As Double
        Dim tDB      As Double
    
        Dim Result() As Double
        Dim MinR     As Double
        Dim MaxR     As Double
    
        Dim scan0    As String
        Dim scan1    As String
    
        W = UBound(Source, 2)
        H = UBound(Source, 3)
        W2 = UBound(toFind, 2)
        H2 = UBound(toFind, 3)
    
        ReDim Result(W , H )
        
        MinR = 1E+32
    
        For X = 0 To W  - W2 Step 4  'To Speed up You can play with Step
            For Y = 0 To H - H2 Step 4
                tDR = 0
                tDG = 0
                tDB = 0
    
                For X2 = 0 To W2 - 1 Step 6  'To Speed up You can play with Step
                    For Y2 = 0 To H2 - 1 Step 6
                        pDR = Source(2, X + X2, Y + Y2)
                        pDG = Source(1, X + X2, Y + Y2)
                        pDB = Source(0, X + X2, Y + Y2)
                        
                        If RGB(pDR, pDG, pDB) = 0 Then 'IF VBBLACK
                        
                            scan0 = scan0 & "1"
                        
                        Else
                            scan0 = scan0 & "0"
                        End If
                        
                        If RGB(toFind(2, X2, Y2), toFind(1, X2, Y2), toFind(0, X2, Y2)) = 0 Then
                            scan1 = scan1 & "1"
                         
                        Else
                            scan1 = scan1 & "0"
                        End If
                  
                    Next
                Next
                
                Result(X, Y) = compareHamming(scan1, scan0)
                scan1 = ""
                scan0 = ""
    
                If Result(X, Y) <= 20 Then
                
                    Form1.Picture1.Line (X, Y)-(X + W2, Y + H2), vbRed, B
                End If
    
                If Result(X, Y) > MaxR Then MaxR = Result(X, Y)
                
                If (Result(X, Y) < MinR) Then
                    MinR = Result(X, Y)
                    X3 = X
                    Y3 = Y
                End If
               
            Next
        Next
        
        MaxR = 255 / MaxR
    
        For X = 0 To W  - W2
            For Y = 0 To H  - H2
    
                Source(2, X, Y) = Result(X, Y) * MaxR
                Source(1, X, Y) = Result(X, Y) * MaxR
                Source(0, X, Y) = Result(X, Y) * MaxR
            Next
        Next
        
        Debug.Print Result(X, Y)
        Form1.Picture1.Line (X3, Y3)-(X3 + W2, Y3 + H2), vbGreen, B
        For X = 0 To W2 
            For Y = 0 To H2 
                Source(2, X3 + X, Y3 + Y) = toFind(2, X, Y)
                Source(1, X3 + X, Y3 + Y) = toFind(1, X, Y)
                Source(0, X3 + X, Y3 + Y) = toFind(0, X, Y)
            Next
        Next
    
    End Sub
    
    
    
    
    Private Function compareHamming(inpA As String, inpB As String)
    
        Dim HD As Long
    
     
        
        HD = Hamming(inpA, inpB)
        
        Select Case HD
      
            MsgBox "Input strings should be of the same length"
        Case -2
            MsgBox "Input 'A' contains invalid characters; should be 0's or 1's"
        Case -3
            MsgBox "Input 'B' contains invalid characters; should be 0's or 1's"
        Case -4
            MsgBox "Both Inputs were invalid"
        Case Else
            compareHamming = HD
        End Select
    
    End Function
    
    Private Function Hamming(ByVal StrA As String, ByVal StrB As String) As Long
    
        Dim TmpBin As String
        Dim i As Long
        
        If Len(StrA) <> Len(StrB) Then
            Hamming = -1
            Exit Function
        End If
        TmpBin = Replace(StrA, "1", "")
        TmpBin = Replace(TmpBin, "0", "")
        If Len(TmpBin) <> 0 Then
            Hamming = -2
        End If
        TmpBin = Replace(StrB, "1", "")
        TmpBin = Replace(TmpBin, "0", "")
    
        If Len(TmpBin) <> 0 Then
            If Hamming = 0 Then 'StrA was valid
                Hamming = -3
            Else
                Hamming = -4
            End If
        End If
        If Hamming <> 0 Then Exit Function
        For i = 1 To Len(StrA)
            If Mid$(StrA, i, 1) <> Mid$(StrB, i, 1) Then
                Hamming = Hamming + 1
            End If
        Next i
        
    End Function
    Case -1Name:  hanm.jpg
Views: 516
Size:  26.7 KB
    Last edited by xxdoc123; Dec 16th, 2021 at 09:53 PM.

  23. #23
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    This know-how is supported in OpenCV. It's called the Template Matching algorithm. Please see the below link.

    https://docs.opencv.org/4.5.1/de/da9..._matching.html

    This algorithm can find a similar object which not needs to be exactly the same. Please see the picture below.

    However, the way to use OpenCV in VB6 is not easy. So, finally, I developed the DLL in C++, then call through VB6 instead. The speed is better than VB6 coding very much, but still got some lack if the main picture is too big.

    I can share my dll for you if need. But if you are still having fun with your research. That's should be fine.

    *I have limited private time. So, will provide the DLL once you ask for it.

    Name:  1639625125381.jpg
Views: 514
Size:  40.6 KB
    Last edited by Taro; Dec 15th, 2021 at 10:39 PM.

  24. #24

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Code:
    Public Function compareStr(sw1 As String, sw2 As String) As Double
        Dim H   As Integer, N As Long
        Dim SB1 As String, SB2 As String
        Debug.Print sw1
        Debug.Print sw2
    
        For H = 1 To Len(sw1)
    
          '  If H = Len(sw1) Then Stop
            SB1 = Mid(sw1, H, 1)
            SB2 = Mid(sw2, H, 1)
    
            If SB1 = SB2 Then
                N = N + 1 'same point
            End If
        Next
        compareStr = N / Len(sw1)
    
        If compareStr = 1 Then
            'MsgBox "Completely similar" & Chr(10) & sw1 & Chr(10) & sw2
        ElseIf compareStr > 0.9 Then
            ' MsgBox "very similar" & Chr(10) & sw1 & Chr(10) & sw2
        ElseIf compareStr > 0.8 Then
            'MsgBox "Basically similar" & Chr(10) & sw1 & Chr(10) & sw2
        Else
            'MsgBox "not similar" & Chr(10) & sw1 & Chr(10) & sw2
        End If
    
    End Function


    'Result(X, Y) = compareHamming(scan1, scan0)

    Result(X, Y) = compareStr(scan1, scan0)
    scan1 = ""
    scan0 = ""

    If Result(X, Y) > 0.96
    Then

    Form2.Picture1.Line (X, Y)-(X + W2, Y + H2), vbRed, B
    End If

    If Result(X, Y) > MaxR Then
    MaxR = Result(X, Y)

    'If (Result(X, Y) < MinR) Then
    'MinR = Result(X, Y)
    X3 = X
    Y3 = Y
    End If

  25. #25

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by Taro View Post
    This know-how is supported in OpenCV. It's called the Template Matching algorithm. Please see the below link.

    https://docs.opencv.org/4.5.1/de/da9..._matching.html

    This algorithm can find a similar object which not needs to be exactly the same. Please see the picture below.

    However, the way to use OpenCV in VB6 is not easy. So, finally, I developed the DLL in C++, then call through VB6 instead. The speed is better than VB6 coding very much, but still got some lack if the main picture is too big.

    I can share my dll for you if need. But if you are still having fun with your research. That's should be fine.

    *I have limited private time. So, will provide the DLL once you ask for it.

    Name:  1639625125381.jpg
Views: 514
Size:  40.6 KB
    openCV Very useful.Did not see the vb code。THANKS YOU .I have sent you a message

  26. #26
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    openCV Very useful.Did not see the vb code。THANKS YOU .I have sent you a message
    Please see below for the project.

    * Make sure your computer has already installed the Visual C++ Redistributable 2017.
    https://docs.microsoft.com/en-us/cpp...?view=msvc-170

    ** If the project does not run. Please contact me anytime. Since never try to run on another computer before.
    *** The project is quite big (from DLLs). So, I upload it to my OneDrive instead.

    Name:  Sample.jpg
Views: 511
Size:  28.2 KB

    https://1drv.ms/u/s!AnNZwQpR8ljsioIW...rScuQ?e=m1uW7P
    Last edited by Taro; Dec 16th, 2021 at 12:24 PM.

  27. #27

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Quote Originally Posted by Taro View Post
    Please see below for the project.

    * Make sure your computer has already installed the Visual C++ Redistributable 2017.
    https://docs.microsoft.com/en-us/cpp...?view=msvc-170

    ** If the project does not run. Please contact me anytime. Since never try to run on another computer before.
    *** The project is quite big (from DLLs). So, I upload it to my OneDrive instead.

    Name:  Sample.jpg
Views: 511
Size:  28.2 KB

    https://1drv.ms/u/s!AnNZwQpR8ljsioIW...rScuQ?e=m1uW7P
    。thanks,project run in my win7 64 ,can not find 。
    Last edited by xxdoc123; Dec 16th, 2021 at 08:20 PM.

  28. #28
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    。thanks,project run in my win7 64 ,can not find 。
    1. Make sure you installed the Visual C++ Redistributable 2017 from the link by previous post.
    2. If can't find. Please copy all OpenCV DLLs from sub folder to project folder.

    Then try again.

  29. #29
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    My project requires the following OpenCV dlls as shown by the below picture.

    Name:  1639715609067.jpg
Views: 485
Size:  33.7 KB
    Last edited by Taro; Dec 16th, 2021 at 11:41 PM.

  30. #30

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    copy all OpenCV DLLs from sub folder to project folder. WORK FINE。 It's so fast.Does IFWOpenCV.dll have other functions

  31. #31
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    copy all OpenCV DLLs from sub folder to project folder. WORK FINE。 It's so fast. Does IFWOpenCV.dll have other functions
    Sure, many of them. BTW, not much time to explain to you. Please check the OpenCV website then tell me which functions of OpenCV you are interested in. I'm not implementing all OpenCV functions since I also developed my own image processing function to serve my software.

  32. #32

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    Yes it is too complicated. What if the image you are looking for is zoomed. Seems to be inaccurate

    Template1.bmp 127x125.is Zoomed to 100x60

  33. #33
    Member Taro's Avatar
    Join Date
    Feb 2014
    Posts
    33

    Re: Image feature recognition algorithm

    Quote Originally Posted by xxdoc123 View Post
    Yes it is too complicated. What if the image you are looking for is zoomed. Seems to be inaccurate

    Template1.bmp 127x125.is Zoomed to 100x60
    So far, most of these functions work with controlled environments e.g. specific cameras, specific sizes of images. If you want a better functions. Please look for FLANN functions or deep learning at:-

    https://docs.opencv.org/4.5.1/d9/d97...eatures2d.html
    https://docs.opencv.org/4.5.1/d2/d58...ntent_dnn.html

    However these functions, they said it is commercial functions that need to pay to use it. So, the normal C++ compiler as I do will skip to compile it. (Or I still have not found the way to work with it.)

    BTW, look that the Python and Linux can work well with it. I never use Python. So, never try that too.

  34. #34

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    thank you

  35. #35

    Thread Starter
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    679

    Re: Image feature recognition algorithm

    I found this algorithm call pHash, but there is no VB6. Who can provide it

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width