Sie sind auf Seite 1von 15

L Th Vinh, Phng o to, Trng HSP K thut Vinh

Ngh An, 5/2013 1


Hng dn s dng VBA trong Excel
1. Gii thiu
Cc phn mm trong MS Office ni chung v Excel ni ring l cng c gip
chng ta lu tr s liu, x l s liu trong qu trnh lm vic rt hiu qu, tit kim
thi gian, cng sc. Ngoi cc hm n gin c trang b sn trong th vin ca
Excel nh hm Sum(), Max(), Min(), Text(), Value(), Left(), Vlookup () Average()
v.v. Ngi s dng c th lp trnh, to ra cc hm, th tc phc tp hn theo nhu cu
s dng bng cch dng cng c VBA (Visual Basic for Application), dng ngn ng
lp trnh VB, nhng vo cc ng dng ca Microsoft nh MS Word, PowerPoint, Auto
CAD v.v. y chng ta vit cc hm, th tc cho Microsoft Excel.
2. Vo ra chng trnh, ci t s dng hm trong Excel
a. Vorachngtrnh
Bc 1. Khi ng Microsoft Excel, to mt workbook mi (hoc dng Book1
nh mc nh). Chn Tools\Macro\Visual Basic Editor m ca s son tho VBA.
Trong ca s Project Explorer (nu khng thy th chn View Project Explorer m
n), chn VBAProject (Book1). Chn Insert Module thm mt module.
Bc 2. G ni dung hm phepcong() vo module mi to.
V d:
Public Function Phepcong(x as double, y as double) as double
Phepcong = x + y
End Function
Bc 3. Chuyn sang ca s Excel kim tra hm bng cch th g vo bt
k, =Phepcong(x,y), kt qu tr v tng ng l x+y. V d: = Phepcong(2,3) kt qu
tr v l 5.
b. Ci t vs dng hmtrongExcel
Bc 1. M t hm thun tin cho vic s dng. Trong ca s Excel, chn
menu Tools\Macro\Macros hin th hp thoi Macro. G tn hm Phepcong vo
Macro name, ri bm Options m tip hp thoi Macro Options, g ni dung m t
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 2
hm vo Description, bm OK ng hp thoi Macro Options, cui cng bm
Cancel ng hp thoi Macro.
Bc 2. Lu Book1 vo my vi tn file, v d MyFunctions.xla; Bn lu file ny
ng v tr mi ln MS Excel khi ng s mc nh a ham vo th vin chung,
sn sng s dng.
V d: Th mc C:\Documents and Settings\Administrator\Application Data\
Microsoft\AddIns i vi MS 2003.
ng MS Excel m khng cn ghi li cc thay i trn Book1.
Bc 3. Dng Windows Explorer thm m t cho Add-in bng cch bm chut
phi trn tn tp tin MyFunctions.xla, chn mc Properties m hp thoi
Properties, chn mc Summary g m t vo Comments, g tn ca Add-in vo
Title. Chn nt OK chp nhn cc thng tin.
Bc 4. Khi ng li MS Excel, ci t add-in va to cho Excel bng cch chn
menu Tools\Add-Ins m hp thoi Add-Ins, chn tn Add-in ca ta trong danh sch
Add-Ins available, ri bm chut vo nt OK.
T y tr v sau, mi ln m MS Excel, mc nh bn c th dng c hm
Phepcong trong Add-in MyFunctions.xla.
3. Lu mt s khi nim
a) Thuc tnh RANGE
Thuc tnh Range tr v mt i tng, c th l mt cell n l hoc mt dy
gm nhiu cell. Trong lnh gn gi tr ca cell A1 vo cell A5 i y, Range tr v
gi tr ch gm 1 cell:
Worksheets("Sheet1").Range("A5").Value =
Worksheets("Sheet1").Range("A1").Value
Khi dng vi kiu khng xc nh, Range tr v mt dy cell trn Sheet ang hot
ng. trnh nhm ln kiu "Ru ng n cm cm b kia", ta kch hot mt bng
tnh bng phng php Activate trc khi dng thuc tnh Range m khng cn ch ra
gii hn c th. Sau y l cch in vo vng A1:H8 cc s ngu nhin bng cch t
cng thc cho mi trong dy m trc Sheet1 c kch hot:
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 3
Worksheets("sheet1").Activate
Range("A1:H8").Formula = "=rand()"
Chng ta c th t tn cho dy cell v ch cho VBA tham chiu n tn ny. V
d, ra lnh xa ni dung ca mt dy c tn "Criteria" chng ta vit:
Worksheets(1).Range("criteria").ClearContents
Nu ta s dng mt i s (argument) m i s l a ch dy cell, th phi
nh r a ch theo kiu A1 (nu dng kiu R1C1 my s bo li).
b) Thuc tnh Cells
Thuc tnh Cells s dng c php Cells(row,column), vi row l ch s hng v
column l ch s ct, tr v mt cell n l. Chng hn, chng ta c th gn gi tr
24 cho cell A1 bng lnh:
Worksheets(1).Cells(1, 1).Value = 24
V gn mt cng thc cho cell A2:
ActiveSheet.Cells(2, 1).Formula = "=sum(b1:b5)"
Cho d chng ta c th dng cng thc Range("A1") tr v cell A1 (khng h
sai!), nhng dng thuc tnh Cells th tin li hn bi bn c th s dng mt bin s
i din cho hng hoc ct phc v yu cu lp trnh. Hy tham kho v d to tiu
ct v hng trn Sheet1 sau y, lu sau khi bng tnh c kch hot, thuc tnh
Cells c th c s dng thoi mi m khng cn khai bo mt sheet c th no v n
tr v mt cell trn sheet hot ng.
Sub SetUpTable()
Worksheets("sheet1").Activate
For theYear = 1 To 5
Cells(1, theYear + 1).Value = 1990 + theYear
Next theYear
For theQuarter = 1 To 4
Cells(theQuarter + 1, 1).Value = "Q" & theQuarter
Next theQuarter
End Sub
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 4
Mc d bn c th s dng nhng hm x l chui ca Visual Basic thay i
tham chiu kiu A1, nhng d hiu hn v rn luyn k nng lp trnh ca mnh,
bn nn s dng kiu Cells(1, 1).
Nu bn s dng c php expression.Cells(row,column), vi expression l mt
biu thc tr v mt i tng Range, v row v column l v tr tng i so vi gc
trn tri ca dy cell th kt qu tr v l mt b phn ca dy. Trong v d di y,
VBA ch n Cell(1,1) tc l cell C5 trn bng tnh:
Worksheets(1).Range("c5:c10").Cells(1, 1).Formula = "=rand()
c) Kt hp Range and Cells
Phi hp Range v Cells tham chiu n mt dy cell, bn hy s dng c
php Range(cell 1, cell 2), vi cell 1 v cell 2 l cell bt u v cell kt thc ca dy.
t kiu ng vin cho cc cell bn dng lnh sau:
With Worksheets(1)
.Range(.Cells(1, 1), .Cells(10, 10)).Borders.LineStyle = xlThick
End With
y cn lu n du chm ng trc thuc tnh Cells. Du chm ny quy
nh Worksheets(1) m With nu trc c p dng cho thuc tnh Cells tit
kim ch v lm cho cu lnh gn hn (nu khng c du chm, thuc tnh Cells tr v
cc cell trn sheet hot ng).
4. Mt s v d
Sau y l mt s v d x l chui v s trong trng hc.
Option Explicit
Dim k As Long
Public luachon As Byte
Public newValue As Double
Public actCell As Range
Public formu As String
Public ass As String
Public first As Boolean
Function SoTCchuadat(Dayheso As Range, Daydiemthi As Range) As
Integer
' Xac dinh Co tin chi Chua dat (co Diem <=0.5)
Dim i As Integer
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 5
SoTCchuadat = 0.5
For i = 1 To Daydiemthi.Columns.Count
If (Daydiemthi.Columns.Cells(1, i) <= 0.5) Then
SoTCchuadat = SoTCchuadat + Dayheso.Columns.Cells(i)
End If
Next i
End Function
Function SoTCTL(Dayheso As Range, Daydiemthi As Range,
TrueORflase As Boolean) As Integer
Dim i As Integer
' Neu TrueORflase=true thi tra ve so Tin chi tich luy
' Neu TrueORflase=flase thi tra ve so Tin chi diem 0
SoTCTL = 0.5
If TrueORflase Then
For i = 1 To Daydiemthi.Columns.Count
If (Daydiemthi.Columns.Cells(1, i) > 0.5) Then
SoTCTL = SoTCTL + Dayheso.Columns.Cells(i)
End If
Next i
Else
For i = 1 To Daydiemthi.Columns.Count
If (Daydiemthi.Columns.Cells(1, i) = 0.5) Then
SoTCTL = SoTCTL + Dayheso.Columns.Cells(i)
End If
Next i
End If
End Function
Public Function Loc(diem As String) As Byte
Dim lan1 As Byte
Dim lan2 As Byte
Dim s As String
If Not KiemtraDiem(diem) Then
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 6
MsgBox " Diem khong hop le"
Loc = 0
Exit Function
End If
For i = 1 To Len(diem)
If Mid(diem, i, 1) <> " " Then s = s & Mid(diem, i, 1)
Next i
diem = s
If KiemtraDiem(diem) Then
If Len(diem) = 4 Then
If Mid(diem, 1, 1) = "(" And Mid(diem, 3, 1) = ")" Then
lan1 = Val(Mid(diem, 2, 1))
lan2 = Val(Mid(diem, 4, 1))
End If
If Mid(diem, 2, 1) = "(" And Mid(diem, 4, 1) = ")" Then
lan1 = Val(Mid(diem, 1, 1))
lan2 = Val(Mid(diem, 3, 1))
End If
If lan1 > lan2 Then
Loc = lan1
Else
Loc = lan2
End If
End If
If Len(diem) = 1 Then Loc = Val(diem)
If diem = "10" Then Loc = 10
If Len(diem) = 5 Then Loc = 10
End If
End Function
Public Function Tinh_TBC(Dayheso As Range, Daydiemthi As Range)
As Double
' Tinh diem Trung binh chung (TBC)
Dim Tongheso As Integer
Dim tam As Double
Dim i As Integer
Dim Nomon As Boolean
Dim tam2 As String
tam = 0
Tongheso = 0
Nomon = False
For i = 1 To Dayheso.Count
If Loc(Daydiemthi.Item(i).Value) < 5 Or
Loc(Daydiemthi.Item(i).Value) > 10 Then
Nomon = True
End If
Tongheso = Tongheso + Dayheso.Item(i).Value
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 7
tam = tam + Dayheso.Item(i).Value *
Loc(Daydiemthi.Item(i).Value)
Next i
If Tongheso = 0 Then Tongheso = 1
Tinh_TBC = Round(tam / Tongheso, 2)
tam2 = Mid(Str(Tinh_TBC), 1, 5)
Tinh_TBC = Val(tam2)
End Function
Public Function Tinh_TBC_XLLop(Dayheso As Range, Daydiemthi As
Range) As Double
' Tinh diem TBC va Xet len lop
Dim Tongheso As Integer
Dim tam As Double
Dim i As Integer
Dim Nomon As Boolean
Dim tam2 As String
tam = 0
Tongheso = 0
Nomon = False
For i = 1 To Dayheso.Count
Tongheso = Tongheso + Dayheso.Item(i).Value
tam = tam + Dayheso.Item(i).Value *
Loc(Daydiemthi.Item(i).Value)
Next i
If Tongheso = 0 Then Tongheso = 1
Tinh_TBC_XLLop = Round(tam / Tongheso, 2)
tam2 = Mid(Str(Tinh_TBC_XLLop), 1, 5)
Tinh_TBC_XLLop = Val(tam2)
End Function
Public Function doidiemTC(Diemso As Double) As String
' Chuyen Thang diem 10 sang Thang diem 4
If Diemso <= 1.9 Then doidiemTC = "0"
If 2 <= Diemso And Diemso <= 3.9 Then doidiemTC = "0.5"
If 4 <= Diemso And Diemso <= 4.4 Then doidiemTC = "1"
If 4.5 <= Diemso And Diemso <= 5.4 Then doidiemTC = "1.5"
If 5.5 <= Diemso And Diemso <= 6.9 Then doidiemTC = "2"
If 7 <= Diemso And Diemso <= 8.4 Then doidiemTC = "3"
If 8.5 <= Diemso And Diemso <= 10 Then doidiemTC = "4"
End Function
Public Function doidiemChu(Diemso As Double) As String
' Doi diem so sang Diem chu
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 8
If Diemso < 1.9 Then doidiemChu = "F"
If 2 <= Diemso And Diemso <= 3.9 Then doidiemChu = "F+"
If 4 <= Diemso And Diemso <= 4.4 Then doidiemChu = "D"
If 4.5 <= Diemso And Diemso <= 5.4 Then doidiemChu = "D+"
If 5.5 <= Diemso And Diemso <= 6.9 Then doidiemChu = "C"
If 7 <= Diemso And Diemso <= 8.4 Then doidiemChu = "B"
If 8.5 <= Diemso And Diemso <= 10 Then doidiemChu = "A"
End Function
Public Function Xeploai(TBC As Double) As String
' Xep loai
If TBC < 5 Then Xeploai = "Khong Dat"
If 5 <= TBC And TBC < 6 Then Xeploai = "Trung binh"
If 6 <= TBC And TBC < 7 Then Xeploai = "Trung binh kha"
If 7 <= TBC And TBC < 8 Then Xeploai = " Kha"
If 8 <= TBC And TBC < 9 Then Xeploai = " Gioi"
If 9 <= TBC And TBC <= 10 Then Xeploai = " Xuat sac"
End Function
Public Function XeploaiTCDiem4(TBC As Double) As String
If TBC < 2 Then TBC = "Khong Dat"
If 2 <= TBC And TBC <= 2.49 Then XeploaiTCDiem4 = "Trung binh"
If 2.5 <= TBC And TBC <= 3.19 Then XeploaiTCDiem4 = "Kha"
If 3.2 <= TBC And TBC <= 3.59 Then XeploaiTCDiem4 = "Gioi"
If 3.6 <= TBC And TBC <= 4 Then XeploaiTCDiem4 = "Xuat sac"
End Function
Public Function Xetlenlop(Sonamdahoc As Byte, DayhesoNam As
Range, DaydiemthiNam As Range, DayhesoKhoa As Range, DaydiemthiKhoa
As Range) As String
' Xet len lop
Dim TBC_Khoa As Double
Dim TBC_Nam As Double
Dim Tongso_DVHT_thieu As Byte
TBC_Nam = Tinh_TBC_XLLop(DayhesoNam, DaydiemthiNam)
TBC_Khoa = Tinh_TBC_XLLop(DayhesoKhoa, DaydiemthiKhoa)
So_DVHT_thieu = 0
For i = 1 To DaydiemthiKhoa.Count
If Loc(DaydiemthiKhoa.Item(i).Value) < 5 Or
Loc(DaydiemthiKhoa.Item(i).Value) > 10 Then
So_DVHT_thieu = So_DVHT_thieu +
DayhesoKhoa.Item(i).Value
End If
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 9
Next i
Tongso_DVHT_thieu = So_DVHT_thieu
If Tongso_DVHT_thieu <= 25 And TBC_Nam >= 5 Then
Xetlenlop = "Ln lp"
Else
If ((Tongso_DVHT_thieu > 25) Or (TBC_Nam < 5)) And ((TBC_Nam
< 3.5) Or (Sonamdahoc = 2 And TBC_Khoa < 4) Or (Sonamdahoc = 3 And
TBC_Khoa < 4.5) Or (Sonamdahoc = 4 And TBC_Khoa < 4.8)) Then
Xetlenlop = "Th"i hc"
Else
Xetlenlop = "Tm ngng hc"
End If
End If
Xetlenlop = Xetlenlop & "; " & TBC_Nam & "; " & TBC_Khoa
& "; " & Tongso_DVHT_thieu
End Function
Public Function TachKetqua(Ketqua As String) As String
t = Ketqua
If Len(Ketqua) < 10 Then
TachKetqua = "'"
Else
For i = 1 To Len(Ketqua)
If Mid(t, i, 1) = ";" Then
TachKetqua = Mid(t, 1, i - 1)
Exit For
End If
Next i
End If
End Function
Public Function TachTBCKhoa(Ketqua As String) As String
If Len(Ketqua) < 10 Then
TachTBCKhoa = ""
Else
For i = 1 To Len(Ketqua)
For j = i + 1 To Len(Ketqua)
If Mid(Ketqua, i, 1) = ";" And Mid(Ketqua, j, 1) =
";" Then
TachTBCKhoa = Mid(Ketqua, i + 1, j - i - 1)
Exit For
End If
Next j
Next i
End If
End Function
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 10
Public Function TachTBCNam(Ketqua As String) As String
If Len(Ketqua) < 10 Then
TachTBCNam = ""
Else
For i = 1 To Len(Ketqua)
If Mid(Ketqua, i, 1) = ";" Then Exit For
Next i
For j = i + 1 To Len(Ketqua)
If Mid(Ketqua, j, 1) = ";" Then Exit For
Next j
TachTBCNam = Mid(Ketqua, i + 1, j - i - 1)
End If
End Function
Public Function TachSoDVHTthieu(Ketqua As String) As String
If Len(Ketqua) < 10 Then
TachSoDVHTthieu = ""
Else
For i = 1 To Len(Ketqua)
If Mid(Ketqua, i, 1) = ";" Then j = i
Next i
TachSoDVHTthieu = Mid(Ketqua, j + 1, Len(Ketqua) - j + 1)
End If
End Function
Public Function KiemtraDiem(diem As String) As Boolean
Dim s As String
For i = 1 To Len(diem)
If Mid(diem, i, 1) <> " " Then s = s & Mid(diem, i, 1)
Next i
diem = s
KiemtraDiem = False
For i = 0 To 10
If diem = i Then
KiemtraDiem = True
Exit Function
End If
Next i
For i = 0 To 10
For j = 0 To 10
If diem = "(" & i & ")" & j Then
KiemtraDiem = True
Exit Function
End If
Next j
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 11
Next i
For i = 0 To 10
For j = 0 To 10
If diem = i & "(" & j & ")" Then
KiemtraDiem = True
Exit Function
End If
Next j
Next i
End Function
Public Function Tach_Ten(Hoten As String) As String
On Error Resume Next
Dim dai As Byte
Dim tam As String
Hoten = Trim(Hoten)
dai = Len(Hoten)
i = dai
Do
If Mid(Hoten, i, 1) = " " Then Exit Do
i = i - 1
Loop Until i = 1
Tach_Ten = Trim(Mid(Hoten, i, dai - i + 1))
End Function
Public Function Tach_Ho(Hoten As String) As String
On Error Resume Next
Dim dai As Byte
Dim tam As String
Hoten = Trim(Hoten)
dai = Len(Hoten)
i = dai
Do
If Mid(Hoten, i, 1) = " " Then Exit Do
i = i - 1
Loop Until i = 1
Tach_Ho = Trim(Mid(Hoten, 1, i - 1))
End Function
Public Function Xet_TC_DuThi(Daydiemthi As Range) As String
Dim Nomon As Boolean
Xet_TC_DuThi = "Ko no mon"
Nomon = False
For i = 1 To Daydiemthi.Count
If Loc(Daydiemthi.Item(i).Value) < 5 Or
Loc(Daydiemthi.Item(i).Value) > 10 Then
Nomon = True
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 12
End If
Next i
If Nomon Then Xet_TC_DuThi = " * No mon *"
End Function
Public Function Tach_Ngay(Ngay As String) As String
On Error Resume Next
Dim dai As Byte
Dim tam As String
Ngay = Trim(Ngay)
dai = Len(Ngay)
i = 1
Do
If Mid(Ngay, i, 1) = "/" Then Exit Do
i = i + 1
Loop Until i = dai
Tach_Ngay = Trim(Mid(Ngay, 1, i + 1))
End Function
Public Function Tinh_TBC_Xet_HocBong(Dayheso As Range, Daydiemthi
As Range, diemRenLuyen As Double) As Double
Dim Tongheso As Integer
Dim tam As Double
Dim tamRL As Double
Dim i As Integer
Dim Nomon As Boolean
Dim tam2 As String
tamRL = diemRenLuyen
tam = 0
Tongheso = 0
Nomon = False
For i = 1 To Dayheso.Count
If Loc_DiemLan1(Daydiemthi.Item(i).Value) < 5 Or
Loc_DiemLan1(Daydiemthi.Item(i).Value) > 10 Then
Nomon = True
End If
Tongheso = Tongheso + Dayheso.Item(i).Value
tam = tam + Dayheso.Item(i).Value *
Loc_DiemLan1(Daydiemthi.Item(i).Value)
Next i
'If Nomon Then MsgBox "C sinh vin: n hc phn hoc im
kh"ng hp l", vbCritical
If Tongheso = 0 Then Tongheso = 1
Tinh_TBC_Xet_HocBong = Round(tam / Tongheso, 2)
tam2 = Mid(Str(Tinh_TBC_Xet_HocBong), 1, 5)
Tinh_TBC_Xet_HocBong = Val(tam2) + tamRL
End Function
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 13
Public Function Loc_DiemLan1(diem As String) As Byte
Dim lan1 As Byte
Dim lan2 As Byte
Dim s As String
If Not KiemtraDiem(diem) Then
'MsgBox " Diem khong hop le"
Loc_DiemLan1 = 0
Exit Function
End If
For i = 1 To Len(diem)
If Mid(diem, i, 1) <> " " Then s = s & Mid(diem, i, 1)
Next i
diem = s
If KiemtraDiem(diem) Then
If Len(diem) = 4 Then
If Mid(diem, 1, 1) = "(" And Mid(diem, 3, 1) = ")" Then
lan1 = Val(Mid(diem, 2, 1))
lan2 = Val(Mid(diem, 4, 1))
End If
If Mid(diem, 2, 1) = "(" And Mid(diem, 4, 1) = ")" Then
lan1 = Val(Mid(diem, 1, 1))
lan2 = Val(Mid(diem, 3, 1))
End If
Loc_DiemLan1 = lan1
End If
If Len(diem) = 1 Then Loc_DiemLan1 = Val(diem)
If diem = "10" Then Loc_DiemLan1 = 10
If Len(diem) = 5 Then Loc_DiemLan1 = 10
End If
End Function
Function MySumx(X As Range) As Double
Dim YY, z, zz As String
z = 0
Dim xzz
For Each YY In X
zz = YY
z = z + abc(zz)
Next YY
MySumx = z
End Function
Function abc(a As String) As String
Dim b, c
b = Pos(a, ")") + 1
c = Mid(a, b, Len(a))
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 14
abc = c
End Function
Private Function Pos(st As String, substr As String) As Long
Dim a, b, c
a = Len(substr)
b = 0
For c = 1 To Len(st) - a + 1
If Mid(st, c, a) = substr Then
b = c
End If
Next c
Pos = b
End Function
Function MySum(Heso As Range, diem As Range, Optional
GiaTriThayThe As Double = 0) As Double
Dim Y As Range, z, zz
z = 0
zz = 0
Dim xzz As String, zxx As Double
For Each Y In diem
zz = zz + 1
xzz = abc(Y.Value)
zxx = Val(xzz)
If (zxx = 0) And (xzz <> "0") Then
zxx = GiaTriThayThe
End If
z = z + zxx * Heso(, zz)
Next Y
MySum = z
End Function
Function MyAverage(Heso As Range, Giatri As Range, Optional BoQua
As Boolean = False) As Double
Dim Y, z, zz, zzz, zxx, xzz
z = 0
zz = 0
zzz = 0
For Each Y In Heso
zz = zz + 1
xzz = abc(Giatri(, zz))
zxx = Val(xzz)
If Not (BoQua And (zxx = 0) And (xzz <> "0")) Then
zzz = zzz + Y
z = z + zxx * Y
End If
Next Y
L Th Vinh, Phng o to, Trng HSP K thut Vinh
Ngh An, 5/2013 15
MyAverage = z / zzz
End Function
Function SoTC0(Dayheso As Range, Daydiemthi As Range) As Integer
'Xac dinh Tong so Tin chi cua cac hoc phan co Diem =0.
Dim i As Integer
SoTC0 = 0
For i = 1 To Daydiemthi.Columns.Count
If (Daydiemthi.Columns.Cells(1, i) = 0) Then
SoTC0 = SoTC0 + Dayheso.Columns.Cells(i)
End If
Next i
End Function
Function TBCTL4(Dayheso As Range, Daydiemthi As Range) As Double
'Ham tinh diem TBCTL thang 4, doi voi cac hoc phan co Diem>=1.0
Dim i As Integer
Dim soTC, tsoTC As Integer
TBCTL4 = 0#
tsoTC = 0
soTC = 0
For i = 1 To Daydiemthi.Columns.Count
If (Daydiemthi.Columns.Cells(1, i) >= 1#) Then
soTC = Dayheso.Columns.Cells(1, i)
TBCTL4 = TBCTL4 + Daydiemthi.Columns.Cells(1, i) *
soTC
tsoTC = tsoTC + soTC
End If
Next i
TBCTL4 = TBCTL4 / tsoTC
End Function
Chc cc bn thnh cng!
Ti liu tham kho: Bn hng dn ny c s dng mt s ti liu t Internet.

Das könnte Ihnen auch gefallen