• Tidak ada hasil yang ditemukan

1. PROGRAM MODUL UTAMA - Temu Kembali Citra Wajah berdasarkan Pengukuran Kemiripan Fitur dengan Menggunakan Jaringan Bayesian

N/A
N/A
Protected

Academic year: 2019

Membagikan "1. PROGRAM MODUL UTAMA - Temu Kembali Citra Wajah berdasarkan Pengukuran Kemiripan Fitur dengan Menggunakan Jaringan Bayesian"

Copied!
33
0
0

Teks penuh

(1)

LAMPIRAN KODE PROGRAM

1.

PROGRAM MODUL UTAMA

'--- ' Program : Modul Utama

' Diprogram : Hendrik Siagian

'--- Public Const eps = 2.2204E-16

Public Const pi = 22 / 7 Public Const deg = pi / 180 Public Const binH = 18 Public Const binS = 3 Public Const binI = 3

Public Const nbinColor = binH * binS * binI Public Const nbinTheta = 72

Public Const Threshold = 255 Public Const NumLevel = 16

Public Type TipeBMP BMPType As String * 2 BMPSize As Long xHotSpot As Integer yHotSpot As Integer OffBites As Long HdrSize As Long Width As Long Height As Long End Type

Public Type TImageRGB Width As Integer Height As Integer Red() As Integer Green() As Integer Blue() As Integer End Type

Public Type TImageHSI Width As Integer Height As Integer H() As Single S() As Single I() As Single End Type

Public Type TImageGray Width As Integer Height As Integer Gray() As Integer End Type

Public Type TImageEdge Width As Integer Height As Integer Edge() As Integer Theta() As Single Bin() As Integer End Type

Public Type TColorHSI H As Single

(2)

Public Type TMatrix Row As Integer Col As Integer Value() As Single End Type

Public Type TRect x1 As Integer y1 As Integer x2 As Integer y2 As Integer End Type

Public Type TipeColor Red As Integer Green As Integer Blue As Integer End Type

Public Type TSimilarity Id As String * 8 Sim As Single End Type

Public Type TGraycoprops Energy As Single Entropy As Single Contrast As Single Correlation As Single Homogenity As Single InvMoment As Single MaxProbability As Single End Type

Public Declare Function GetPixel Lib "gdi32" (ByVal hdc As Long, _ ByVal x As Long, ByVal y As Long) As Long

Public Declare Function SetPixel Lib "gdi32" (ByVal hdc As Long, _ ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long

Public bmpX As Integer '-- Dimensi Citra Public bmpY As Integer

Public ImgFileName As String

Public IROption As Integer '-- Opsi Image Retrieval Public AdaCapture As Boolean

Public NFileQuery As String Public NIDFace As Integer

Public NFImgSource As String '-- Nama File Sumber Citra Wajah

'--- ' IMGREAD :Fungsi untuk membaca data warna citra dari kontrol Picture ' dan menyimpannya ke dalam variabel bertipe struktur array RGB ' hdc : kontrol Picture; x = picture width; y = picture height

'--- Public Function ImgRead(ByVal hdc As Long, ByVal x As Integer, _ ByVal y As Integer) As TImageRGB

Dim r As Integer Dim c As Integer Dim nColor As Long

(3)

ReDim ImgRead.Blue(x, y) For c = 0 To x - 1 For r = 0 To y - 1

nColor = GetPixel(hdc, c, r)

ImgRead.Red(c, r) = nColor And RGB(255, 0, 0)

ImgRead.Green(c, r) = (nColor And RGB(0, 255, 0)) / 256 ImgRead.Blue(c, r) = (nColor And RGB(0, 0, 255)) / 256 / 256 Next r

Next c End Function

'--- ' IMGCROP :Fungsi untuk membaca sebagiandata warna citra dari ' kontrol Picture dan menyimpannya ke dalam variabel bertipe ' struktur array RGB hdc : kontrol Picture;

' x1 = kolom pojok kiri atas; y1 = baris pojok kiri atas ' x2 = kolom pojok kanan bawah; y1 = baris pojok kanan bawah '--- Public Function ImgCrop(ByVal hdc As Long, ByVal x1 As Integer, _ ByVal y1 As Integer, ByVal x2 As Integer, _ ByVal y2 As Integer) As TImageRGB

Dim r As Integer Dim c As Integer Dim nColor As Long

Dim nW As Integer '-- lebar kolom cropping Dim nH As Integer '-- tinggi baris cropping

nW = Abs(x2 - x1) nH = Abs(y2 - y1)

ImgCrop.Width = nW ImgCrop.Height = nH

ReDim ImgCrop.Red(nW, nH) ReDim ImgCrop.Green(nW, nH) ReDim ImgCrop.Blue(nW, nH) For c = 0 To nW - 1

For r = 0 To nH - 1

nColor = GetPixel(hdc, x1 + c, y1 + r)

ImgCrop.Red(c, r) = nColor And RGB(255, 0, 0)

ImgCrop.Green(c, r) = (nColor And RGB(0, 255, 0)) / 256 ImgCrop.Blue(c, r) = (nColor And RGB(0, 0, 255)) / 256 / 256 Next r

Next c End Function

'--- ' IMGSHOW : Subprogram untuk menampilkan citra ke kontrol Picture ' berdasarkan data warna citra dari variabel bertipe struktur array RGB ' hdc : kontrol Picture; w = picture width; h = picture height

'--- Public Sub ImgShow(ByVal hdc As Long, ByRef Img As TImageRGB)

Dim W As Integer Dim H As Integer Dim nColor As Long

Dim c As Integer '-- pencacah kolom Dim r As Integer '-- pencacah tinggi Dim p As Long

W = Img.Width H = Img.Height For c = 0 To W - 1 For r = 0 To H - 1

(4)

Next r Next c End Sub

'--- ' Program Konversi Desimal ke Heksadesimal ' dengan lebar format tampilan w karakter '---

Public Function DeciToHex(Desi As Integer, W As Byte) As String Dim BKar As Integer

Dim nResult As String nResult = Hex(Desi) BKar = Len(nResult) If W > BKar Then

nResult = String(W - BKar, "0") & nResult End If

DeciToHex = nResult End Function

'--- 'BMPRead : Membaca data RGB dari suatu file Bitmap (*.BMP) ' secara langsung

'--- Public Function BMPRead(FileName As String) As TImageRGB Dim RekBMP As TipeBMP

Dim vFile As Integer Dim nData As Long Dim bmpX As Integer Dim bmpY As Integer Dim nPixel As Long Dim n As Long Dim p As Long Dim c As Integer Dim r As Integer Dim DataBMP() As Byte

'---Membaca header file bmp vFile = FreeFile

Open FileName For Random As #vFile Get #vFile, , RekBMP

Close #vFile

'---Membaca Data BMP nData = FileLen(FileName) ReDim DataBMP(nData)

Open FileName For Binary As #vFile Get #vFile, , DataBMP

Close #vFile

'---Menyusun Data BMP ke Matrik RGB bmpX = RekBMP.Width

bmpY = RekBMP.Height BMPRead.Width = bmpX BMPRead.Height = bmpY

ReDim BMPRead.Red(bmpX, bmpY) ReDim BMPRead.Green(bmpX, bmpY) ReDim BMPRead.Blue(bmpX, bmpY) nPixel = bmpX * bmpY

c = 0 r = 0

p = RekBMP.OffBites For n = 1 To nPixel c = c + 1

(5)

If c = bmpX Then c = 0

r = r + 1 End If p = p + 3 Next n p = 0

Erase DataBMP End Function

'--- ' ArcCos : Fungsi untuk menentukan nilai Invers Cosinus '--- Public Function ArcCos(x As Single) As Single

ArcCos = (Atn(-x / (Sqr(1 - x ^ 2) + eps)) + 2 * Atn(1)) / (2 * pi) End Function

'--- ' MIN : Fungsi untuk menentukan bilangan terkecil dari dua ' bilangan X dan Y

'--- Public Function Min(x As Integer, y As Integer) As Integer If x < y Then

Min = x Else Min = y End If End Function

'--- 'RGBtoHSI : Fungsi mengkonversi Warna RGB ke ruang ' warna HSI

'--- Public Function RGBtoHSI(cRGB As Long) As TColorHSI Dim r As Integer

Dim G As Integer Dim B As Integer Dim num As Single Dim den As Single Dim Theta As Single Dim H As Single Dim S As Single Dim I As Single

r = CInt(cRGB And RGB(255, 0, 0))

G = CInt((cRGB And RGB(0, 255, 0)) / 256) B = CInt((cRGB And RGB(0, 0, 255)) / 256 / 256)

num = 0.5 * ((r - G) + (r - B))

den = Sqr((r - G) ^ 2 + CSng((r - B)) * CSng((G - B))) Theta = ArcCos(num / (den + eps))

H = Theta If B > G Then

H = 2 * pi - Theta End If

H = H / (2 * pi)

num = Min(Min(r, G), B) den = r + G + B

(6)

S = 1 - 3 * num / den I = ((r + G + B) / 3) / 255 RGBtoHSI.H = H

RGBtoHSI.S = S RGBtoHSI.I = I End Function

'--- 'ImageRGBToHSI : Konversi Citra RGB ke Citra HSI

'--- Public Function ImageRGBToHSI(imgRGB As TImageRGB) As TImageHSI Dim c As Integer

Dim r As Integer Dim cRGB As Long Dim cHSI As TColorHSI

ImageRGBToHSI.Width = imgRGB.Width ImageRGBToHSI.Height = imgRGB.Height

ReDim ImageRGBToHSI.H(imgRGB.Width, imgRGB.Height) ReDim ImageRGBToHSI.S(imgRGB.Width, imgRGB.Height) ReDim ImageRGBToHSI.I(imgRGB.Width, imgRGB.Height)

For c = 1 To imgRGB.Width For r = 1 To imgRGB.Height

cRGB = RGB(imgRGB.Red(c, r), _ imgRGB.Green(c, r), _ imgRGB.Blue(c, r)) cHSI = RGBtoHSI(cRGB)

ImageRGBToHSI.H(c, r) = cHSI.H ImageRGBToHSI.S(c, r) = cHSI.S ImageRGBToHSI.I(c, r) = cHSI.I Next r

Next c End Function

'--- 'binHistoHSI : Menentukan posisi bin pada Histogram HSI ' sesuai dengan banyak bin H, S dan I '---

Public Function binHistoHSI(cHSI As TColorHSI, nbinH As Integer, _ nbinS As Integer, nbinI As Integer) As Integer Dim rH As Single '--range bin

Dim rS As Single Dim rI As Single Dim nbH As Integer Dim nbS As Integer Dim nbI As Integer Dim nbin As Integer

rH = 1 / (nbinH - 1) rS = 1 / (nbinS - 1) rI = 1 / (nbinI - 1)

nbH = CInt(cHSI.H / rH) nbS = Int(cHSI.S / rS) nbI = Int(cHSI.I / rI)

nbin = (nbH * nbinS * nbinI) + (nbS * nbinI) + nbI + 1 binHistoHSI = nbin

End Function

'--- ' HistogramHSI : Membangun histogram HSI dari suatu citra HSI ' sesuai dengan banyak bin H, S dan I

(7)

Public Function HistogramHSI(imgHSI As TImageHSI, nbinH As Integer, _ nbinS As Integer, nbinI As Integer) As TMatrix Dim nbin As Integer

Dim n As Integer Dim c As Integer Dim r As Integer Dim p As Single Dim cHSI As TColorHSI

nbin = nbinH * nbinS * nbinI HistogramHSI.Col = 2

HistogramHSI.Row = nbin

ReDim HistogramHSI.Value(2, nbin) For n = 1 To nbin

HistogramHSI.Value(1, n) = n HistogramHSI.Value(2, n) = 0 Next n

For c = 1 To imgHSI.Width For r = 1 To imgHSI.Height cHSI.H = imgHSI.H(c, r) cHSI.S = imgHSI.S(c, r) cHSI.I = imgHSI.I(c, r)

n = binHistoHSI(cHSI, 18, 3, 3) p = HistogramHSI.Value(2, n) p = p + 1

HistogramHSI.Value(2, n) = p Next r

Next c

'--- Normalisasi p = 0

For n = 1 To nbin

p = p + HistogramHSI.Value(2, n) Next n

For n = 1 To nbin

HistogramHSI.Value(2, n) = HistogramHSI.Value(2, n) / p Next n

End Function

'--- ' GetColorFeature : Fungsi untuk memperoleh fitur warna ' dari sebuah file citra bitmap (*.BMP) '--- Public Function GetColorFeature(NFile As String, _

nbinH As Integer, nbinS As Integer, nbinI As Integer) _ As TMatrix

Dim imgFace As TImageRGB Dim imgFaceHSI As TImageHSI

imgFace = BMPRead(NFile)

imgFaceHSI = ImageRGBToHSI(imgFace)

GetColorFeature = HistogramHSI(imgFaceHSI, nbinH, nbinS, nbinI) End Function

'--- 'CosineSim : Mengukur jarak dua vektor dengan menggunakan ' Cosine similarity

'---

Public Function CosineSim(A As TMatrix, B As TMatrix, nCol As Integer) As Single

(8)

SigmaA = 0 SigmaB = 0 SigmaAB = 0

For r = 1 To a.Row

SigmaA = SigmaA + (A.Value(nCol, r)) ^ 2 SigmaB = SigmaB + (B.Value(nCol, r)) ^ 2

SigmaAB = SigmaAB + A.Value(nCol, r) * B.Value(nCol, r) Next r

temp = Sqr(SigmaA) * Sqr(SigmaB) If temp = 0 Then

CosineSim = 0 Else

CosineSim = SigmaAB / temp End If

End Function

'--- 'RGBtoGray : Fungsi mengkonversi Warna RGB ke Warna ' Grayscale

'--- Public Function RGBtoGray(cRGB As Long) As Integer Dim r As Integer

Dim G As Integer Dim B As Integer

r = cRGB And RGB(255, 0, 0)

G = (cRGB And RGB(0, 255, 0)) / 256 B = (cRGB And RGB(0, 0, 255)) / 256 / 256

RGBtoGray = CInt(0.299 * r + 0.587 * G + 0.114 * B) End Function

'--- 'ImageRGBToGray : Konversi citra RGB ke citra Gray '---

Public Function ImageRGBToGray(imgRGB As TImageRGB) As TImageGray Dim c As Integer

Dim r As Integer Dim cRGB As Long Dim cGray As Integer

ImageRGBToGray.Width = imgRGB.Width ImageRGBToGray.Height = imgRGB.Height

ReDim ImageRGBToGray.Gray(imgRGB.Width, imgRGB.Height)

For c = 1 To imgRGB.Width For r = 1 To imgRGB.Height

cRGB = RGB(imgRGB.Red(c, r), _ imgRGB.Green(c, r), _ imgRGB.Blue(c, r)) cGray = RGBtoGray(cRGB)

ImageRGBToGray.Gray(c, r) = cGray Next r

Next c End Function

'--- 'BinTheta : Menentukan posisi bin berdasarkan sudut Theta ' dan banyak bin sudut

'---

Public Function binTheta(Theta As Single, nbinTheta As Integer) As Integer Dim stepDeg As Single

stepDeg = 360 / nbinTheta

(9)

'--- 'EdgeSobel : Fungsi mendeteksi tepi dengan metode Sobel '---

Public Function EdgeDetectSobel(Img As TImageGray, Threshold As Integer) As TImageEdge

Dim r As Integer Dim c As Integer Dim Gx As Integer Dim Gy As Integer Dim G As Integer Dim Theta As Single

EdgeDetectSobel.Width = Img.Width EdgeDetectSobel.Height = Img.Height

ReDim EdgeDetectSobel.Edge(Img.Width, Img.Height) ReDim EdgeDetectSobel.Theta(Img.Width, Img.Height) ReDim EdgeDetectSobel.Bin(Img.Width, Img.Height)

For c = 1 To Img.Width For r = 1 To Img.Height

EdgeDetectSobel.Edge(c, r) = 0 Next r

Next c

For c = 2 To Img.Width - 1 For r = 2 To Img.Height - 1

Gx = (Img.Gray(c - 1, r + 1) + _ 2 * Img.Gray(c, r + 1) + _ Img.Gray(c + 1, r + 1)) - _ (Img.Gray(c - 1, r - 1) + _ 2 * Img.Gray(c, r - 1) + _ Img.Gray(c + 1, r - 1))

Gy = (Img.Gray(c + 1, r - 1) + _ 2 * Img.Gray(c + 1, r) + _ Img.Gray(c + 1, r + 1)) - _ (Img.Gray(c - 1, r - 1) + _ 2 * Img.Gray(c - 1, r) + _ Img.Gray(c - 1, r + 1)) G = Abs(Gx) + Abs(Gy)

If G > Threshold Then

EdgeDetectSobel.Edge(c, r) = 1 End If

Theta = Atn(Gy / (Gx + eps)) / deg

EdgeDetectSobel.Theta(c, r) = CInt(Theta)

EdgeDetectSobel.Bin(c, r) = binTheta(Theta, nbinTheta) Next r

Next c End Function

'--- 'CreateShapeVector : Membangun Vektor Shape / Fitur Shape '---

Public Function CreateShapeVector(Img As TImageEdge, nbinTheta As Integer) As TMatrix

Dim c As Integer Dim r As Integer Dim p As Integer Dim np As Single Dim stepDeg As Single

CreateShapeVector.Col = 3

(10)

ReDim CreateShapeVector.Value(3, nbinTheta) stepDeg = 360 / nbinTheta

For r = 1 To nbinTheta

CreateShapeVector.Value(1, r) = r

CreateShapeVector.Value(2, r) = (-180 + r * stepDeg) CreateShapeVector.Value(3, r) = 0

Next r

For c = 1 To Img.Width For r = 1 To Img.Height

p = binTheta(Img.Theta(c, r), nbinTheta) np = CreateShapeVector.Value(3, p) np = np + 1

CreateShapeVector.Value(3, p) = np Next r

Next c

'--- Normalisasi np = 0

For r = 1 To nbinTheta

np = np + CreateShapeVector.Value(3, r) Next r

For r = 1 To nbinTheta

CreateShapeVector.Value(3, r) = CreateShapeVector.Value(3, r) / np Next r

End Function

'--- 'GetShapeFeature : Memperoleh fitur bentuk (shape) ' dari citra bitmap (BMP)

'--- Public Function GetShapeFeature(NFile As String, _

nbinTheta As Integer, Threshold As Integer) As TMatrix Dim imgFace As TImageRGB

Dim imgGray As TImageGray Dim imgEdge As TImageEdge

imgFace = BMPRead(NFile)

imgGray = ImageRGBToGray(imgFace)

imgEdge = EdgeDetectSobel(imgGray, Threshold)

GetShapeFeature = CreateShapeVector(imgEdge, nbinTheta) End Function

'--- ' GrayScaleMatrix : Fungsi mengubah citra Gray

' ke dalam beberapa tingkat keabuan ' (citra GrayScale)

'--- Public Function GrayScaleMatrix(imgGray As TImageGray, _ Level As Integer) As TImageGray

Dim rangeLevel As Integer Dim binGray As TImageGray Dim c As Integer

Dim r As Integer

rangeLevel = 256 \ Level binGray.Width = imgGray.Width binGray.Height = imgGray.Height

ReDim binGray.Gray(binGray.Width, binGray.Height)

For c = 1 To binGray.Width For r = 1 To binGray.Height

(11)

Next c

GrayScaleMatrix = binGray End Function

'--- ' GrayCoMatrix : Fungsi membentuk Cooccurence Matrix '--- Public Function GrayCoMatrix(imgGray As TImageGray, _

Level As Integer, dy As Integer, dx As Integer) As TImageGray Dim r As Integer

Dim c As Integer Dim startR As Integer Dim startC As Integer Dim endR As Integer Dim endC As Integer Dim q1 As Integer Dim q2 As Integer Dim M As Integer Dim n As Integer

M = imgGray.Height n = imgGray.Width

GrayCoMatrix.Width = Level GrayCoMatrix.Height = Level

ReDim GrayCoMatrix.Gray(Level, Level)

startR = 1 startC = 1

If Sgn(dy) = -1 Then startR = Abs(dy - 1) If Sgn(dy) = -1 Then startC = Abs(dx - 1)

endR = M endC = n

If Sgn(dx) = 1 Then endC = n - dx If Sgn(dy) = 1 Then endC = M - dy

'--- Cooccurence Matrix

For r = 1 To GrayCoMatrix.Height For c = 1 To GrayCoMatrix.Width GrayCoMatrix.Gray(c, r) = 0 Next c

Next r

For r = startR To endR For c = startC To endC q1 = imgGray.Gray(c, r)

q2 = imgGray.Gray(c + dx, r + dy)

GrayCoMatrix.Gray(q1, q2) = GrayCoMatrix.Gray(q1, q2) + 1 Next c

Next r End Function

'--- ' GrayCoMatrixNormal : Fungsi membentuk normalisasi ' Cooccurence Matrix

'---

Public Function GrayCoMatrixNormal(gcom As TImageGray) As TMatrix Dim nlevel As Integer

Dim gcomNormal As TImageGray Dim r As Integer

Dim c As Integer Dim rP As Single

(12)

GrayCoMatrixNormal.Row = nlevel GrayCoMatrixNormal.Col = nlevel

ReDim GrayCoMatrixNormal.Value(nlevel, nlevel)

rP = 0

For r = 1 To nlevel For c = 1 To nlevel

rP = rP + gcom.Gray(c, r) Next c

Next r

If rP = 0 Then rP = rP + eps

'--- Normalisasi matriks cooccurence For r = 1 To nlevel

For c = 1 To nlevel

GrayCoMatrixNormal.Value(c, r) = gcom.Gray(c, r) / rP Next c

Next r End Function

'--- 'Graycoprops : Fungsi menentuk properti berdasarkan ' Cooccurence Matrix Normalisasi

'---

Public Function Graycoprops(gcom As TMatrix) As TGraycoprops Dim nlevel As Integer

Dim rEntropy As Single Dim rEnergy As Single Dim rContrast As Single Dim rHomogenity As Single Dim rInvMoment As Single Dim rMaxProbability As Single Dim rCorrelation As Single Dim r As Integer

Dim c As Integer Dim p As Single Dim PMax As Single

rEntropy = 0 rEnergy = 0 rContrast = 0 rHomogenity = 0 rInvMoment = 0 rMaxProbability = 0 rCorrelation = 0

nlevel = gcom.Row

'--- Menghitung Properti PMax = 0

For r = 1 To nlevel For c = 1 To nlevel p = gcom.Value(c, r)

rEntropy = rEntropy + p * (Log(p + eps)) / Log(10) rEnergy = rEnergy + p ^ 2

rContrast = rContrast + (r - c) ^ 2 * p

rHomogenity = rHomogenity + p / (1 + Abs(r - c)) If Not (r = c) Then

rInvMoment = rInvMoment + p ^ 2 / Abs(r - c) End If

PMax = Max(PMax, p) Next c

Next r

rMaxProbability = PMax

rCorrelation = Correlation(gcom)

(13)

Graycoprops.Energy = rEnergy Graycoprops.Contrast = rContrast Graycoprops.Homogenity = rHomogenity Graycoprops.InvMoment = rInvMoment

Graycoprops.MaxProbability = rMaxProbability Graycoprops.Correlation = rCorrelation End Function

'--- ' Correlation : Menghitung nilai korelasi dari suatu ' gray coocurence matrix

'--- Public Function Correlation(gco As TMatrix) As Single Dim nlevel As Integer

Dim c As Integer Dim r As Integer Dim gcor As TMatrix Dim f As Single Dim uvf As Single Dim n As Single Dim svf As Single Dim sv2f As Single Dim suvf As Single Dim suf As Single Dim su2f As Single

nlevel = gco.Col gcor.Col = nlevel + 5 gcor.Row = nlevel + 5

ReDim gcor.Value(gcor.Col, gcor.Row) For c = 1 To nlevel + 5

For r = 1 To nlevel + 5 gcor.Value(c, r) = 0 Next r

Next c

For r = 1 To nlevel For c = 1 To nlevel

gcor.Value(c, r) = gco.Value(c, nlevel - r + 1) 'gcor.Value(c, r) = gco.Value(c, r)

Next c Next r

For r = 1 To nlevel

gcor.Value(nlevel + 1, r) = nlevel \ 2 - r gcor.Value(r, nlevel + 1) = (-nlevel \ 2) + r Next r

For r = 1 To nlevel f = 0

For c = 1 To nlevel

f = f + gcor.Value(c, r) Next c

gcor.Value(nlevel + 2, r) = f Next r

For c = 1 To nlevel f = 0

For r = 1 To nlevel

f = f + gcor.Value(c, r) Next r

gcor.Value(c, nlevel + 2) = f Next c

For r = 1 To nlevel

(14)

gcor.Value(nlevel + 2, r)

gcor.Value(nlevel + 4, r) = gcor.Value(nlevel + 1, r) ^ 2 * _ gcor.Value(nlevel + 2, r)

uvf = 0

For c = 1 To nlevel

uvf = uvf + gcor.Value(c, nlevel + 1) * gcor.Value(nlevel + 1, r) * _

gcor.Value(c, r) Next c

gcor.Value(nlevel + 5, r) = uvf Next r

For c = 1 To nlevel

gcor.Value(c, nlevel + 3) = gcor.Value(c, nlevel + 1) * _ gcor.Value(c, nlevel + 2)

gcor.Value(c, nlevel + 4) = gcor.Value(c, nlevel + 1) ^ 2 * _ gcor.Value(c, nlevel + 2)

uvf = 0

For r = 1 To nlevel

uvf = uvf + gcor.Value(c, nlevel + 1) * gcor.Value(nlevel + 1, r) * _

gcor.Value(c, r) Next r

gcor.Value(c, nlevel + 5) = uvf Next c

n = 0: svf = 0: sv2f = 0: suvf = 0 For r = 1 To nlevel

n = n + gcor.Value(nlevel + 2, r) svf = svf + gcor.Value(nlevel + 3, r) sv2f = sv2f + gcor.Value(nlevel + 4, r) suvf = suvf + gcor.Value(nlevel + 5, r) Next r

gcor.Value(nlevel + 2, nlevel + 1) = n gcor.Value(nlevel + 3, nlevel + 1) = svf gcor.Value(nlevel + 4, nlevel + 1) = sv2f gcor.Value(nlevel + 5, nlevel + 1) = suvf

n = 0: suf = 0: su2f = 0: suvf = 0

For c = 1 To nlevel

n = n + gcor.Value(c, nlevel + 2) suf = suf + gcor.Value(c, nlevel + 3) su2f = su2f + gcor.Value(c, nlevel + 4) suvf = suvf + gcor.Value(c, nlevel + 5) Next c

gcor.Value(nlevel + 1, nlevel + 2) = n gcor.Value(nlevel + 1, nlevel + 3) = suf gcor.Value(nlevel + 1, nlevel + 4) = su2f gcor.Value(nlevel + 1, nlevel + 5) = suvf

Correlation = (n * suvf - suf * svf) / (Sqr(n * su2f - suf ^ 2) _ * Sqr(n * sv2f - svf ^ 2))

End Function

'--- 'GetTextureFeature : Memperoleh fitur Textur dari ' citra bitmap (*.BMP)

'--- Public Function GetTextureFeature(NFile As String, _ NumLevel As Integer) As TGraycoprops

(15)

Dim Igco0 As TImageGray Dim Igco45 As TImageGray Dim Igco90 As TImageGray Dim Igco135 As TImageGray Dim Ngco0 As TMatrix Dim Ngco45 As TMatrix Dim Ngco90 As TMatrix Dim Ngco135 As TMatrix Dim gcoP0 As TGraycoprops Dim gcoP45 As TGraycoprops Dim gcoP90 As TGraycoprops Dim gcoP135 As TGraycoprops Dim AgcoP As TGraycoprops

imgFace = BMPRead(NFile)

imgGray = ImageRGBToGray(imgFace)

imgGraySc = GrayScaleMatrix(imgGray, NumLevel)

Igco0 = GrayCoMatrix(imgGraySc, NumLevel, 0, 1) Igco45 = GrayCoMatrix(imgGraySc, NumLevel, -1, 1) Igco90 = GrayCoMatrix(imgGraySc, NumLevel, -1, 0) Igco135 = GrayCoMatrix(imgGraySc, NumLevel, -1, -1)

Ngco0 = GrayCoMatrixNormal(Igco0) Ngco45 = GrayCoMatrixNormal(Igco45) Ngco90 = GrayCoMatrixNormal(Igco90) Ngco135 = GrayCoMatrixNormal(Igco135)

gcoP0 = Graycoprops(Ngco0) gcoP45 = Graycoprops(Ngco45) gcoP90 = Graycoprops(Ngco90) gcoP135 = Graycoprops(Ngco135)

AgcoP.Contrast = (gcoP0.Contrast + gcoP45.Contrast + _ gcoP90.Contrast + gcoP135.Contrast) / 4 AgcoP.Correlation = (gcoP0.Correlation + gcoP45.Correlation + _ gcoP90.Correlation + gcoP135.Correlation) / 4 AgcoP.Energy = (gcoP0.Energy + gcoP45.Energy + _

gcoP90.Energy + gcoP135.Energy) / 4 AgcoP.Entropy = (gcoP0.Entropy + gcoP45.Entropy + _ gcoP90.Entropy + gcoP135.Entropy) / 4 AgcoP.Homogenity = (gcoP0.Homogenity + gcoP45.Homogenity + _ gcoP90.Homogenity + gcoP135.Homogenity) / 4 AgcoP.InvMoment = (gcoP0.InvMoment + gcoP45.InvMoment + _ gcoP90.InvMoment + gcoP135.InvMoment) / 4

AgcoP.MaxProbability = (gcoP0.MaxProbability + gcoP45.MaxProbability + _ gcoP90.MaxProbability + gcoP135.MaxProbability) / 4 GetTextureFeature = AgcoP

End Function

'--- ' Max : Fungsi untuk menentukan nilai terbesar dari dua ' buah bilangan

'--- Public Function Max(Bil1 As Single, Bil2 As Single) As Single Max = Bil1

If Bil2 > Bil1 Then Max = Bil2 End Function

'--- ' FeatureVector : Konversi Properti Tekstur ke vektor

' Tekstur

(16)

TextureVector.Row = 7

ReDim TextureVector.Value(TextureVector.Col, TextureVector.Row) TextureVector.Value(1, 1) = gtf.Contrast

TextureVector.Value(1, 2) = gtf.Correlation TextureVector.Value(1, 3) = gtf.Energy TextureVector.Value(1, 4) = gtf.Entropy TextureVector.Value(1, 5) = gtf.Homogenity TextureVector.Value(1, 6) = gtf.InvMoment TextureVector.Value(1, 7) = gtf.MaxProbability End Function

Sub Main() NIDFace = 100 IROption = 4 AdaCapture = False frmMain.Show End Sub

2.

PROGRAM FORM UTAMA

'--- ' Program : Form Main

' Jendela Utama Aplikasi FIR ' Diprogram : Hendrik Siagian

'---

Dim NFCapture As String

Private Sub MDIForm_Load() mnuBayesian.Checked = True mnuSave.Enabled = False mnuRetrieval.Enabled = False mnuViewOut.Enabled = False End Sub

Private Sub mnuAbout_Click() frmAbout.Show

End Sub

Private Sub mnuNew_Click() frmKanvas.ResetKanvas mnuOpen.Enabled = True mnuViewOut.Enabled = False mnuRetrieval.Enabled = False End Sub

Private Sub mnuOpen_Click() cdlFile.ShowOpen

ImgFileName = cdlFile.FileName With frmKanvas

.Caption = ImgFileName

.txtFileName.Text = ImgFileName

.picImage.Picture = LoadPicture(ImgFileName) .picImage.AutoSize = True

(17)

mnuRetrieval.Enabled = True End Sub

Private Sub mnuOption_Click() ChangeFileLink

End Sub

Private Sub mnuSave_Click()

Dim nfFace As String '-- nama file citra wajah key Dim nfKoneksi As String '-- nama file koneksi

Dim vfKoneksi As Integer '-- variabel file koneksi Dim nfSource As String '-- nama file citra sumber Dim stIdFace As String

Dim stPosisi As String

'-- Menyimpan file citra wajah

stIdFace = Trim(frmKanvas.txtIdFace.Text) stPosisi = Trim(frmKanvas.txtPosition) stPosisi = Replace(stPosisi, "-", ", ")

nfSource = Trim(frmKanvas.txtFileName.Text)

nfFace = App.Path & "\FaceBMP\" & Trim(frmKanvas.txtIdFace.Text) & ".bmp" SavePicture frmKanvas.picFace.Image, nfFace

'-- Mengupdate file koneksi vfKoneksi = FreeFile

nfKoneksi = App.Path & "\ConnectDB.dat" Open nfKoneksi For Append As vfKoneksi

Print #vfKoneksi, stIdFace; ", "; nfSource; ", "; stPosisi

Close #vfKoneksi

'-- Tambahkan informasi bahwa penyimpanan sukses

mnuSave.Enabled = False End Sub

Private Sub mnuExit_Click() End

End Sub

Private Sub mnuFaceCapture_Click() frmKanvas.shpCapture.Visible = True End Sub

Private Sub mnuIndexing_Click() 'mnuOpen.Enabled = True frmIndexing.Show

End Sub

'Private Sub mnuRetrieval_Click() ' mnuImgRetrieval.Enabled = True ' frmImageRet.Show

'End Sub

(18)

mnuViewOut.Enabled = True IROption = 1

frmImageRet.Show frmViewOut.Show Unload frmImageRet End Sub

Private Sub mnuShape_Click() mnuColor.Checked = False mnuShape.Checked = True mnuTexture.Checked = False mnuBayesian.Checked = False mnuViewOut.Enabled = True IROption = 2

frmImageRet.Show frmViewOut.Show Unload frmImageRet End Sub

Private Sub mnuTexture_Click() mnuColor.Checked = False mnuShape.Checked = False mnuTexture.Checked = True mnuBayesian.Checked = False mnuViewOut.Enabled = True IROption = 3

frmImageRet.Show frmViewOut.Show Unload frmImageRet End Sub

Private Sub mnuBayesian_Click() mnuColor.Checked = False mnuShape.Checked = False mnuTexture.Checked = False mnuBayesian.Checked = True mnuViewOut.Enabled = True IROption = 4

frmImageRet.Show frmViewOut.Show Unload frmImageRet End Sub

Private Sub mnuViewOut_Click() frmViewOut.Show

End Sub

'--- ' Konversi file link

Private Sub ChangeFileLink() Dim nfSource As String Dim vfSource As Integer Dim nfDest As String Dim vfDest As String Dim IdFace As Integer Dim IdSource As Integer Dim idfaceD As String * 8 Dim idSourceD As String * 8

(19)

Open nfSource For Input As #vfSource

nfDest = App.Path & "\filelinkX.txt" vfDest = FreeFile

Open nfDest For Output As #vfDest

Do While Not EOF(vfSource)

Input #vfSource, IdFace, IdSource idfaceD = "face" & DeciToHex(IdFace, 4) idSourceD = "DSC-" & DeciToHex(IdSource, 4) Print #vfDest, idfaceD; ", "; idSourceD Loop

Close #vfSource Close #vfDest End Sub

3.

PROGRAM FORM KANVAS

'--- ' Program : Form Kanvas

' Kanvas untuk menampilkan citra wajah query ' Diprogram : Hendrik Siagian

'---

Dim CaptureStatus As Integer Dim HScreen As Integer Dim WScreen As Integer Dim stCoord As String Dim FaceImage As TImageRGB Dim FaceBox As TRect

Private Sub Form_Resize() WScreen = Me.ScaleWidth HScreen = Me.ScaleHeight If WScreen < 350 Then Exit Sub If HScreen < 100 Then Exit Sub

picKanvas.Width = WScreen - fraFace.Width - vsbKanvas.Width - 2 picKanvas.Height = HScreen - hsbKanvas.Height - 2

vsbKanvas.Left = picKanvas.Width vsbKanvas.Height = picKanvas.Height hsbKanvas.Width = picKanvas.Width hsbKanvas.Top = picKanvas.Height + 1

fraFace.Left = picKanvas.Width + vsbKanvas.Width + 2 picFace.Left = fraFace.Left

If picImage.Width < picKanvas.Width Then hsbKanvas.Enabled = False

hsbKanvas.Value = 0 Else

hsbKanvas.Enabled = True End If

If picImage.Height < picKanvas.Height Then vsbKanvas.Enabled = False

vsbKanvas.Value = 0 Else

vsbKanvas.Enabled = True End If

CaptureStatus = 0 End Sub

(20)

picFace.Picture = Nothing txtFileName.Text = "" txtIdFace.Text = "" txtPosition.Text = "" CaptureStatus = 0

shpCapture.Visible = False End Sub

Private Sub picImage_KeyUp(KeyCode As Integer, Shift As Integer) Me.Caption = KeyCode

Select Case KeyCode

Case 67: Me.Caption = "Capture ... sukses" txtPosition.Text = stCoord

CaptureStatus = 3

FaceImage = ImgCrop(picImage.hdc, FaceBox.x1 + 1, _

FaceBox.y1 + 1, FaceBox.x2 - 1, FaceBox.y2 - 1) ImageShow FaceImage

frmMain.mnuSave.Enabled = True

Case 27: Me.Caption = "Capture ... abort" CaptureStatus = 0

picFace.Picture = Nothing End Select

End Sub

Private Sub ImageShow(Img As TImageRGB) Dim W As Integer

Dim H As Integer Dim nColor As Long

Dim c As Integer '-- pencacah kolom Dim r As Integer '-- pencacah tinggi Dim p As Long

W = Img.Width H = Img.Height

picFace.BorderStyle = 0 picFace.Width = W picFace.Height = H For c = 0 To W - 1 For r = 0 To H - 1

nColor = RGB(Img.Red(c, r), Img.Green(c, r), Img.Blue(c, r)) picFace.PSet (c, r), nColor

Next r Next c End Sub

Private Sub picImage_MouseUp(Button As Integer, Shift As Integer, x As Single, y As Single)

If CaptureStatus = 1 Then CaptureStatus = 2 End If

End Sub

Private Sub picImage_MouseMove(Button As Integer, Shift As Integer, x As Single, y As Single)

If CaptureStatus = 0 Then shpCapture.Left = x shpCapture.Top = y End If

If Button = 1 Then

If CaptureStatus = 0 Then CaptureStatus = 1 End If

(21)

If CaptureStatus = 1 Then

shpCapture.Width = Abs(x - shpCapture.Left) shpCapture.Height = Abs(y - shpCapture.Top) FaceBox.x1 = shpCapture.Left

FaceBox.y1 = shpCapture.Top

FaceBox.x2 = FaceBox.x1 + shpCapture.Width FaceBox.y2 = FaceBox.y1 + shpCapture.Height

stCoord = FaceBox.x1 & ", " & FaceBox.y1 & "-" & _ FaceBox.x2 & ", " & FaceBox.y2

End If End Sub

Private Sub txtIdFace_KeyUp(KeyCode As Integer, Shift As Integer) If KeyCode = 13 Then

picImage.SetFocus End If

End Sub

Private Sub vsbKanvas_Change() picImage.Top = -vsbKanvas.Value End Sub

Private Sub hsbKanvas_Change() picImage.Left = -hsbKanvas.Value End Sub

4.

PROGRAM FORM REINDEX FITUR CITRA

'--- ' Program : Form Indexing

' Reindex fitur-fitur citra wajah kunci ' Diprogram : Hendrik Siagian

'---

Private Type TColorFeature Id As String * 8

Value(nbinColor) As Single End Type

Private Type TShapeFeature Id As String * 8

Value(nbinTheta) As Single End Type

Private Type TTextureFeature Id As String * 8

Value(7) As Single End Type

Dim n As Integer

Private Sub cmdCancel_Click() Unload Me

End Sub

Private Sub cmdOK_Click() n = 0

tmrTunda.Enabled = True End Sub

(22)

Dim NFile As String n = n + 1

NFile = App.Path & "\Face\face" & DeciToHex(n, 4) & ".bmp" imgFace.Picture = LoadPicture(NFile)

lblReindex.Caption = "Extract Feature From : " & NFile CreateDBColorFeature NFile, n

CreateDBShapeFeature NFile, n CreateDBTextureFeature NFile, n If n = NIDFace Then

tmrTunda.Enabled = False n = 0

MsgBox "Reindex Finished!", vbOKOnly + vbInformation, "Confirmation" Unload Me

End If End Sub

'--- ' Membangun data base fitur warna dari semua ' citra wajah

'---

Private Sub CreateDBColorFeature(NFile As String, nRec As Integer) Dim r As Integer

Dim IdFace As String * 8 Dim gcf As TMatrix Dim nFileDB As String Dim vFileDB As Integer

Dim RecColorF As TColorFeature Dim pRec As Integer

nFileDB = App.Path & "\Feature\ColorF.txt" vFileDB = FreeFile

pRec = Len(RecColorF)

Open nFileDB For Random As #vFileDB Len = pRec IdFace = "face" & DeciToHex(nRec, 4)

gcf = GetColorFeature(NFile, binH, binS, binI) RecColorF.Id = IdFace

For r = 1 To gcf.Row

RecColorF.Value(r) = gcf.Value(2, r) Next r

Put #vFileDB, nRec, RecColorF Close #vFileDB

End Sub

'--- ' Membangun data base fitur bentuk (shape dari semua ' citra wajah

'---

Private Sub CreateDBShapeFeature(NFile As String, nRec As Integer) Dim r As Integer

Dim IdFace As String * 8 Dim gsf As TMatrix Dim nFileDB As String Dim vFileDB As Integer

Dim RecShapeF As TShapeFeature Dim pRec As Integer

nFileDB = App.Path & "\Feature\ShapeF.txt" vFileDB = FreeFile

pRec = Len(RecShapeF)

Open nFileDB For Random As #vFileDB Len = pRec IdFace = "face" & DeciToHex(nRec, 4)

(23)

For r = 1 To gsf.Row

RecShapeF.Value(r) = gsf.Value(3, r) Next r

Put #vFileDB, nRec, RecShapeF Close #vFileDB

End Sub

'--- ' Membangun data base fitur Texture dari semua

' citra wajah

'---

Private Sub CreateDBTextureFeature(NFile As String, nRec As Integer) Dim r As Integer

Dim IdFace As String * 8 Dim gtf As TGraycoprops Dim tf As TMatrix Dim nFileDB As String Dim vFileDB As Integer

Dim RecTextureF As TTextureFeature Dim pRec As Integer

nFileDB = App.Path & "\Feature\TextureF.txt" vFileDB = FreeFile

pRec = Len(RecTextureF)

Open nFileDB For Random As #vFileDB Len = pRec IdFace = "face" & DeciToHex(nRec, 4)

gtf = GetTextureFeature(NFile, NumLevel) tf = TextureVector(gtf)

RecTextureF.Id = IdFace

For r = 1 To tf.Row

RecTextureF.Value(r) = tf.Value(1, r) Next r

Put #vFileDB, nRec, RecTextureF Close #vFileDB

End Sub

5.

PROGRAM FORM IMAGE RETRIEVAL

'--- ' Program : Form Imager Retrieval

' Menyusu Ranking hasil temu-kembali citra wajah ' Diprogram : Hendrik Siagian

'---

Private Type TColorFeature Id As String * 8

Value(nbinColor) As Single End Type

Private Type TShapeFeature Id As String * 8

Value(nbinTheta) As Single End Type

Private Type TTextureFeature Id As String * 8

(24)

Private Sub Form_Load() Select Case IROption

Case 1: Me.Caption = "Searching with Color Fiture" Case 2: Me.Caption = "Searching with Shape Fiture" Case 3: Me.Caption = "Searching with Texture Fiture" Case 4: Me.Caption = "Searching with Bayesian Methode" End Select

If AdaCapture = False Then NFileQuery = ImgFileName End If

lblQuery = "Query : " & NFileQuery Select Case IROption

Case 1: ColorImageRetrieval NFileQuery

SortFile App.Path & "\Output\IROutC.txt" Case 2: ShapeImageRetrieval NFileQuery

SortFile App.Path & "\Output\IROutS.txt" Case 3: TextureImageRetrieval NFileQuery

SortFile App.Path & "\Output\IROutT.txt" Case 4: BayesImageRetrieval NFileQuery

SortFile App.Path & "\Output\IROutB.txt" 'SortFile App.Path & "\Output\IROutC.txt" 'SortFile App.Path & "\Output\IROutS.txt" 'SortFile App.Path & "\Output\IROutT.txt" End Select

End Sub

'--- ' ColorImageRetrieval : Temu Kembali Citra berdasarkan ' Warna (Color)

'--- Private Sub ColorImageRetrieval(NFile As String)

Dim gcfQuery As TMatrix Dim gcfLib As TMatrix Dim nfColor As String Dim vfColor As Integer

Dim RecColorF As TColorFeature Dim nfIROut As String

Dim vfIROut As Integer Dim RecSim As TSimilarity Dim nRec As Integer Dim r As Integer Dim ColorSim As Single

gcfQuery = GetColorFeature(NFile, binH, binS, binI) gcfLib.Col = 2

gcfLib.Row = nbin

ReDim gcfLib.Value(2, nbinColor)

nfColor = App.Path & "\Feature\ColorF.txt" vfColor = FreeFile

Open nfColor For Random As #vfColor Len = Len(RecColorF)

nfIROut = App.Path & "\Output\IROutC.txt" vfIROut = FreeFile

Open nfIROut For Random As #vfIROut Len = Len(RecSim)

nRec = 0

Do While Not EOF(vfColor) nRec = nRec + 1

Get #vfColor, nRec, RecColorF For r = 1 To nbinColor

gcfLib.Value(1, r) = r

gcfLib.Value(2, r) = RecColorF.Value(r) Next r

(25)

RecSim.Sim = ColorSim Put #vfIROut, nRec, RecSim Loop

Close #vfColor Close #vfIROut End Sub

'--- ' ShapeImageRetrieval : Temu Kembali Citra berdasarkan ' Bentuk (Shape)

'--- Private Sub ShapeImageRetrieval(NFile As String)

Dim gsfQuery As TMatrix Dim gsfLib As TMatrix Dim nfShape As String Dim vfShape As Integer

Dim RecShapeF As TShapeFeature Dim nfIROut As String

Dim vfIROut As Integer Dim RecSim As TSimilarity Dim nRec As Integer Dim r As Integer Dim ShapeSim As Single

gsfQuery = GetShapeFeature(NFile, nbinTheta, Threshold)

gsfLib.Col = 3 gsfLib.Row = nbin

ReDim gsfLib.Value(3, nbinTheta)

nfShape = App.Path & "\Feature\ShapeF.txt" vfShape = FreeFile

Open nfShape For Random As #vfShape Len = Len(RecShapeF)

nfIROut = App.Path & "\Output\IROutS.txt" vfIROut = FreeFile

Open nfIROut For Random As #vfIROut Len = Len(RecSim)

nRec = 0

Do While Not EOF(vfShape) nRec = nRec + 1

Get #vfShape, nRec, RecShapeF For r = 1 To nbinTheta

gsfLib.Value(1, r) = r

gsfLib.Value(3, r) = RecShapeF.Value(r) Next r

ShapeSim = CosineSim(gsfQuery, gsfLib, 3) RecSim.Id = RecShapeF.Id

RecSim.Sim = ShapeSim Put #vfIROut, nRec, RecSim Loop

Close #vfShape Close #vfIROut End Sub

'--- ' TextureImageRetrieval : Temu Kembali Citra berdasarkan ' Tekstur (Texture)

'--- Private Sub TextureImageRetrieval(NFile As String) Dim gtfQuery As TGraycoprops

(26)

Dim RecTextureF As TTextureFeature Dim nfIROut As String

Dim vfIROut As Integer Dim RecSim As TSimilarity Dim nRec As Integer Dim r As Integer

Dim TextureSim As Single

gtfQuery = GetTextureFeature(NFile, NumLevel) tfQuery = TextureVector(gtfQuery)

gtfLib.Col = tfQuery.Col gtfLib.Row = tfQuery.Row

ReDim gtfLib.Value(tfQuery.Col, tfQuery.Row)

nfTexture = App.Path & "\Feature\TextureF.txt" vfTexture = FreeFile

Open nfTexture For Random As #vfTexture Len = Len(RecTextureF)

nfIROut = App.Path & "\Output\IROutT.txt" vfIROut = FreeFile

Open nfIROut For Random As #vfIROut Len = Len(RecSim)

nRec = 0

Do While Not EOF(vfTexture) nRec = nRec + 1

Get #vfTexture, nRec, RecTextureF For r = 1 To gtfLib.Row

gtfLib.Value(1, r) = RecTextureF.Value(r) Next r

TextureSim = CosineSim(tfQuery, gtfLib, 1) RecSim.Id = RecTextureF.Id

RecSim.Sim = TextureSim Put #vfIROut, nRec, RecSim Loop

Close #vfTexture Close #vfIROut End Sub

'--- ' BayesImageRetrieval : Temu Kembali Citra berdasarkan ' Metode Bayesian

'--- Private Sub BayesImageRetrieval(NFile As String)

Dim nfIRColor As String Dim nfIRShape As String Dim nfIRTexture As String Dim nfIROut As String Dim vfIRColor As Integer Dim vfIRShape As Integer Dim vfIRTexture As Integer Dim vfIROut As Integer Dim RecSim As TSimilarity Dim pRec As Integer Dim nRec As Integer Dim n As Integer Dim SimColor As Single Dim SimShape As Single Dim SimTexture As Single Dim SimBayes As Single

(27)

nfIRColor = App.Path & "\Output\IROutC.txt" nfIRShape = App.Path & "\Output\IROutS.txt" nfIRTexture = App.Path & "\Output\IROutT.txt" nfIROut = App.Path & "\Output\IROutB.txt"

pRec = Len(RecSim)

nRec = FileLen(nfIRColor) / pRec vfIRColor = FreeFile

Open nfIRColor For Random As #vfIRColor Len = pRec

vfIRShape = FreeFile

Open nfIRShape For Random As #vfIRShape Len = pRec

vfIRTexture = FreeFile

Open nfIRTexture For Random As #vfIRTexture Len = pRec

vfIROut = FreeFile

Open nfIROut For Random As #vfIROut Len = pRec

For n = 1 To nRec

Get #vfIRColor, n, RecSim SimColor = RecSim.Sim Get #vfIRShape, n, RecSim SimShape = RecSim.Sim Get #vfIRTexture, n, RecSim SimTexture = RecSim.Sim

SimBayes = 1 - ((1 - SimColor) * _ (1 - SimShape) * _ (1 - SimTexture)) RecSim.Sim = SimBayes

Put #vfIROut, n, RecSim Next n

Close #vfIRColor Close #vfIRShape Close #vfIRTexture Close #vfIROut End Sub

'--- ' SortFile : Mengurutkan file output berdasarkan ' nilai similarity

'--- Private Sub SortFile(NFile As String)

Dim RecSim As TSimilarity Dim pRec As Integer Dim nRec As Integer Dim vFile As Integer Dim n As Integer Dim x As Integer Dim y As Integer

Dim RSim() As TSimilarity

pRec = Len(RecSim)

nRec = FileLen(NFile) / pRec ReDim RSim(nRec)

vFile = FreeFile

Open NFile For Random As #vFile Len = pRec n = 0

Do While Not EOF(vFile) n = n + 1

If n > nRec Then Exit Do Get #vFile, n, RSim(n) Loop

(28)

'--- Swap Sort

For x = 1 To nRec - 1 For y = x + 1 To nRec

If RSim(x).Sim < RSim(y).Sim Then RecSim = RSim(x)

RSim(x) = RSim(y) RSim(y) = RecSim End If

Next y Next x

'--- Simpan ulang hasil sort

Open NFile For Random As #vFile Len = pRec For n = 1 To nRec

Put #vFile, n, RSim(n) Next n

Close #vFile End Sub

6.

PROGRAM FORM VIEWOUT

'--- ' Program : Form View Out

' Menampilkan hasil temu-kembali citra wajah ' Diprogram : Hendrik Siagian

'---

Dim HScreen As Integer Dim WScreen As Integer Dim WSpace As Integer Dim HSpace As Integer Dim WImg As Integer Dim HImg As Integer

Private Sub Form_Activate() Select Case IROption

Case 1: Me.Caption = "Searching with Color Fiture" DisplayIROut (App.Path & "\Output\IROutC.txt") Case 2: Me.Caption = "Searching with Shape Fiture" DisplayIROut (App.Path & "\Output\IROutS.txt") Case 3: Me.Caption = "Searching with Texture Fiture" DisplayIROut (App.Path & "\Output\IROutT.txt") Case 4: Me.Caption = "Searching with Bayesian Methode" DisplayIROut (App.Path & "\Output\IROutB.txt") End Select

End Sub

Private Sub Form_Resize() Dim n As Integer Dim nLeft As Integer Dim nTop As Integer

WScreen = Me.ScaleWidth HScreen = Me.ScaleHeight If WScreen < 350 Then Exit Sub If HScreen < 180 Then Exit Sub WSpace = 20

HSpace = 20

WImg = (WScreen - 12 * WSpace) / 11 HImg = (HScreen - 9 * WSpace) / 5

(29)

lblRanking(n).Top = nTop lblRanking(n).Left = nLeft lblRanking(n).Width = 1.5 * WImg lblRanking(n).Alignment = 2

lblIdFace(n).Top = lblRanking(n).Top + lblRanking(n).Height lblIdFace(n).Left = nLeft

lblIdFace(n).Width = 1.5 * WImg lblIdFace(n).Alignment = 2

imgOut(n).Top = lblIdFace(n).Top + lblIdFace(n).Height imgOut(n).Left = nLeft

imgOut(n).Width = 1.5 * WImg imgOut(n).Height = 1.5 * HImg nLeft = 4 * WSpace + 3 * WImg Else

lblRanking(n).Top = nTop + 2 * HSpace lblRanking(n).Left = nLeft

lblRanking(n).Width = WImg lblRanking(n).Alignment = 2

lblIdFace(n).Top = lblRanking(n).Top + lblRanking(n).Height lblIdFace(n).Left = nLeft

lblIdFace(n).Width = WImg lblIdFace(n).Alignment = 2

imgOut(n).Top = lblIdFace(n).Top + lblIdFace(n).Height imgOut(n).Left = nLeft

imgOut(n).Width = WImg imgOut(n).Height = HImg nLeft = nLeft + WSpace + WImg End If

Next n

nTop = imgOut(0).Top + imgOut(0).Height + HSpace nLeft = WSpace

For n = 1 To 11

lblRanking(8 + n).Top = nTop lblRanking(8 + n).Left = nLeft lblRanking(8 + n).Width = WImg lblRanking(8 + n).Alignment = 2

lblIdFace(8 + n).Top = lblRanking(8 + n).Top + lblRanking(8 + n).Height

lblIdFace(8 + n).Left = nLeft lblIdFace(8 + n).Width = WImg lblIdFace(8 + n).Alignment = 2

imgOut(8 + n).Top = lblIdFace(8 + n).Top + lblIdFace(8 + n).Height imgOut(8 + n).Left = nLeft

imgOut(8 + n).Width = WImg imgOut(8 + n).Height = HImg

lblRanking(19 + n).Top = imgOut(8 + n).Top + imgOut(8 + n).Height + HSpace

lblRanking(19 + n).Left = nLeft lblRanking(19 + n).Width = WImg lblRanking(19 + n).Alignment = 2

lblIdFace(19 + n).Top = lblRanking(19 + n).Top + lblRanking(19 + n).Height

lblIdFace(19 + n).Left = nLeft lblIdFace(19 + n).Width = WImg lblIdFace(19 + n).Alignment = 2

(30)

imgOut(19 + n).Width = WImg imgOut(19 + n).Height = HImg nLeft = nLeft + WSpace + WImg Next n

'DisplayOutputIR

End Sub

'--- 'DisplayIROut : Subprogram untuk menampilkan output 'Data Hasil pencarian dibaca dari file IROut

'sesuai dengan fitur (Color, Shape, Texture atau 'Bayesian)

'--- Private Sub DisplayIROut(NFile As String)

Dim vFile As Integer Dim RecSim As TSimilarity Dim pRec As Integer Dim nRec As Integer Dim n As Integer Dim stRank As String

pRec = Len(RecSim) nRec = FileLen(NFile)

imgOut(0).Stretch = True

imgOut(0).Picture = LoadPicture(NFileQuery) imgOut(0).Visible = True

stRank = "Image" & vbCrLf & "Query" lblRanking(0).Caption = stRank lblRanking(0).Visible = True lblIdFace(0).Caption = ""

vFile = FreeFile

Open NFile For Random As #vFile Len = pRec n = 0

Do While Not (EOF(vFile)) n = n + 1

Get #vFile, n, RecSim

stRank = n & vbCrLf & RecSim.Sim imgOut(n).Stretch = True

imgOut(n).Picture = LoadPicture(App.Path & _

"\Face\" & RecSim.Id & ".bmp") lblRanking(n).Alignment = 2

lblRanking(n).Caption = stRank lblIdFace(n).Alignment = 2 lblIdFace(n).Caption = RecSim.Id lblRanking(n).Visible = True lblIdFace(n).Visible = True imgOut(n).Visible = True If n >= 30 Then Exit Do Loop

Close #vFile End Sub

Private Sub imgOut_Click(Index As Integer) Dim stIdFace As String

If Index > 0 Then

stIdFace = lblIdFace(Index).Caption

If Not (Trim(SearchImageSource(stIdFace)) = "") Then NFImgSource = App.Path & "\Picture\" & _

SearchImageSource(stIdFace) & ".jpg" frmMain.Enabled = False

(31)

End If End If End Sub

'--- 'SearchImageSource : Fungsi untuk mencari path dan nama file 'sesuai denga IdFace

'--- Private Function SearchImageSource(sId As String) As String Dim NFile As String

Dim vFile As Integer Dim IdFace As String Dim IdSource As String

vFile = FreeFile

NFile = App.Path & "\FileLink.txt" Open NFile For Input As #vFile SearchImageSource = ""

Do While Not (EOF(vFile))

Input #vFile, IdFace, IdSource If Trim(sId) = Trim(IdFace) Then SearchImageSource = IdSource Exit Do

End If Loop

Close #vFile End Function

7.

PROGRAM FORM IMAGE SOURCE

'--- ' Program : Form Image Source ' Menampilkan citra sumber wajah ' Diprogram : Hendrik Siagian

'---

Dim stShpFace As Integer Dim HScreen As Integer Dim WScreen As Integer

Private Sub Form_Load() Me.Caption = NFImgSource

picSource.Picture = LoadPicture(NFImgSource) picSource.AutoSize = True

bmpX = picSource.Width bmpY = picSource.Height stShpFace = 0

End Sub

Private Sub Form_Resize() WScreen = Me.ScaleWidth HScreen = Me.ScaleHeight If WScreen < 350 Then Exit Sub If HScreen < 100 Then Exit Sub

picKanvas.Width = WScreen - vsbKanvas.Width - 2 picKanvas.Height = HScreen - hsbKanvas.Height - 2 vsbKanvas.Left = picKanvas.Width

vsbKanvas.Height = picKanvas.Height hsbKanvas.Width = picKanvas.Width hsbKanvas.Top = picKanvas.Height + 1 End Sub

(32)

frmMain.Enabled = True End Sub

Private Sub vsbKanvas_Change() picSource.Top = -vsbKanvas.Value End Sub

Private Sub hsbKanvas_Change() picSource.Left = -hsbKanvas.Value End Sub

'Private Sub picSource_KeyUp(KeyCode As Integer, Shift As Integer) ' If KeyCode = 67 Then

' shpFace.Left = FacePos.x1 ' shpFace.Top = FacePos.y1

' shpFace.Width = FacePos.x2 - FacePos.x1 ' shpFace.Height = FacePos.y2 - FacePos.y1 ' If stShpFace = 0 Then

' shpFace.Visible = True ' stShpFace = 1

' Else

' shpFace.Visible = False ' stShpFace = 0

' End If ' End If 'End Sub

8.

PROGRAM FORM ABOUT

'--- ' Program : Form About

' Menampilkan layar bergulung ucapan terimakasih ' Diprogram : Hendrik Siagian

'---

Dim Ucapan As String Dim Judul As String Dim p As Integer

Private Sub Form_Load()

Judul = "Temu Kembali Citra Wajah Berdasarkan" & vbCrLf Judul = Judul & "Pengukuran Kemiripan Fitur Dengan" & vbCrLf Judul = Judul & "Menggunakan Jaringan Bayesian"

lblJudul.Caption = Judul

imgLogo.Picture = LoadPicture(App.Path & "\LogoFIKTI.jpg") imgPenulis.Picture = LoadPicture(App.Path & "\FotoPenulis.jpg") imgLogo.Visible = True

imgPenulis.Visible = False

Ucapan = "Atas selesainya penulisan tesis ini, " & vbCrLf

Ucapan = Ucapan & "penulis mengucapkan terimakasih dan penghormatan " & vbCrLf

Ucapan = Ucapan & "setinggi-tingginya kepada: " & vbCrLf & vbCrLf Ucapan = Ucapan & "KOMISI PEMBIMBING:" & vbCrLf

Ucapan = Ucapan & "1. Bapak Dr. POLTAK SIHOMBING, MKom. dan" & vbCrLf Ucapan = Ucapan & "2. Bapak Prof. DR. Muhammad Zarlis" & vbCrLf

Ucapan = Ucapan & "Atas pengarahan dan dorongan yang telah diberikan " Ucapan = Ucapan & "sehingga memberi inspirasi bagi penulis untuk membuat " Ucapan = Ucapan & "aplikasi ini." & vbCrLf & vbCrLf

Ucapan = Ucapan & "PENGUJI TESIS :" & vbCrLf

(33)

Ucapan = Ucapan & "yang diberikan." & vbCrLf & vbCrLf & vbCrLf

Ucapan = Ucapan & "Secara khusus penulis juga mengucapkan TERIMA KASIH kepada :" & vbCrLf

Ucapan = Ucapan & "Bapak M. ANDRI BUDIMAN, S.T., M.Comp.Sc., M.E.M. " & vbCrLf

Ucapan = Ucapan & "Atas Dorongan Semangat dan Solusi yang diberikan" & vbCrLf

Ucapan = Ucapan & "tidak akan pernah dilupakan. Terimakasih atas e-book nya." & vbCrLf & vbCrLf

Ucapan = Ucapan & "Terimakasih juga untuk Seluruh Dosen, Staf, Karyawan dan " & vbCrLf

Ucapan = Ucapan & "rekan-rekan mahasiwa di Fakultas Ilmu Komputer dan " & vbCrLf

Ucapan = Ucapan & "Teknologi Informasi - USU atas kerjasama yang baik." & vbCrLf & vbCrLf

Ucapan = Ucapan & "Untuk Istri Tercinta Ir. Dra. Ellen Tampubolon MSi., terimaksih " & vbCrLf

Ucapan = Ucapan & "atas kesabarannya." & vbCrLf & vbCrLf Ucapan = Ucapan & "Dari" & vbCrLf

Ucapan = Ucapan & "HENDRIK SIAGIAN" & vbCrLf Ucapan = Ucapan & "NIM: 107038003" & vbCrLf

Ucapan = Ucapan & "PROGRAM STUDI MAGISTER (S2) TEKNIK INFORMATIKA" & vbCrLf

Ucapan = Ucapan & "FAKULTAS ILMU KOMPUTER DAN TEKNOLOGI INFORMASI" & vbCrLf

Ucapan = Ucapan & "UNIVERSITAS SUMATERA UTARA " Ucapan = Ucapan & "MEDAN" & vbCrLf

Ucapan = Ucapan & "2013" & vbCrLf Ucapan = Ucapan & "---" & vbCrLf

p = 100 End Sub

Private Sub Form_Activate()

Me.Left = (Screen.Width - Me.Width) \ 2 Me.Top = (Screen.Height - Me.Height) \ 2 tmrTunda.Enabled = True

lblUcapan.Caption = Ucapan End Sub

Private Sub Form_Unload(Cancel As Integer) frmMain.Enabled = True

Unload Me End Sub

Private Sub cmdTutup_Click() frmMain.Enabled = True Unload Me

End Sub

Private Sub tmrTunda_Timer()

imgLogo.Visible = Not imgLogo.Visible imgPenulis.Visible = Not imgPenulis.Visible End Sub

Private Sub tmrGulung_Timer() p = p - 3

Referensi

Dokumen terkait

Dalam hal istri tidak mau memberikan persetujuan, dan permohonan izin untuk beristri lebih dari satu orang berdasarkan atas salah satu alasan yang diatur dalam pasal 55 ayat (2)

Hasil: Infusa daun rambutan memiliki aktivitas larvasida dengan konsentrasi efektif sebesar 50% yang menyebabkan mortalitas larva 97% serta tidak memiliki perbedaan yang

telah menemukan bahwa risiko terjadinya katarak subkapsular posterior adalah yang paling rendah pada mereka yang memiliki lutein dengan konsentrasi yang lebih

Ilustrasi cover ini terdiri dari pesan visual dan pesan verbal, dimana pesan visual ini berupa lima orang laki – laki yang dilihat dari kontur mereka adalah sebagai tokoh

Berdasarkan pembahasan pada bab sebelumnya, dapat ditarik kesimpulan bahwa faktor-faktor yang mempenga- ruhi kinerja guru IPA SMP di Kecamatan Ngaglik adalah

[r]

(10) Setiap orang atau badan yang menemukan adanya kegiatan pengumpulan sumbangan uang atau barang yang diindikasikan tidak mempunyai izin, atau dilakukan dengan pemaksaan

Rasio likuiditas menunjukkan kemampuan perusahaan untuk memenuhi kewajibannya dalam jangka pendek. Perusahaan dalam keadaan likuid apabila perusahaan mampu memenuhi