Sub 変数使用1() Dim endr As Integer Dim i As Integer timck = Timer Application.ScreenUpdating = False ThisWorkbook.Activate Sheets("Sheet1").Select endr = Range("B10000").End(xlUp).Row For i = 1 To endr Sheets("Sheet2").Cells(i, 1) = Sheets("Sheet1").Cells(i, 1) Sheets("Sheet2").Cells(i, 2) = Sheets("Sheet1").Cells(i, 2) Next Sheets("Sheet1").Select Range("A1").Select Application.CutCopyMode = False Application.ScreenUpdating = True MsgBox "マクロ処理時間⇒ " & Timer - timck & "秒" End Sub |
|
Sub 変数使用2() Dim endr As Integer Dim mydat As Variant Application.ScreenUpdating = False ThisWorkbook.Activate Sheets("Sheet1").Select endr = Range("B10000").End(xlUp).Row mydat = Range(Cells(1, 1), Cells(endr, 2)) Sheets("Sheet2").Select Range(Cells(1, 1), Cells(endr, 2)).Value = mydat Sheets("Sheet1").Select Range("A1").Select End Sub |
Sub 変数使用3() Dim endr As Integer Dim myrng As Range Application.ScreenUpdating = False ThisWorkbook.Activate Sheets("Sheet1").Select endr = Range("B10000").End(xlUp).Row Set myrng = Range(Cells(1, 1), Cells(endr, 2)) Sheets("Sheet2").Select Range(Cells(1, 1), Cells(endr, 2)).Value = myrng.Value Sheets("Sheet1").Select Range("A1").Select End Sub |
Sub 変数使用4() Dim endr As Integer Application.ScreenUpdating = False ThisWorkbook.Activate Sheets("Sheet1").Select endr = Range("B10000").End(xlUp).Row Range("A1:B" & endr & "").Select Selection.Copy Sheets("Sheet2").Select Range("A1").Select ActiveSheet.Paste Range("C1").Select Sheets("Sheet1").Select Range("A1").Select Application.CutCopyMode = False End Sub |
Sub 変数使用5() Dim i As Integer ThisWorkbook.Sheets("Sheet3").Select For i = 1 To 15000 Cells(i, 1) = i Next Sheets("Sheet1").Select End Sub ------------------------------------------------------ Sub 変数使用6() Dim i As Variant ThisWorkbook.Sheets("Sheet3").Select For i = 1 To 15000 Cells(i, 1) = i Next Sheets("Sheet1").Select End Sub |
Sub シート関数1() Dim i As Integer, mymax(1) As Integer ThisWorkbook.Sheets("Sheet3").Select endr = Range("A31000").End(xlUp).Row For i = 2 To endr If mymax(1) < Cells(i, 1) Then mymax(1) = Cells(i, 1) mymax(0) = i End If Next End Sub |
Sub シート関数2() Dim i As Integer, mymax(1) As Integer Dim myrng As Range, chk As Range ThisWorkbook.Sheets("Sheet3").Select endr = Range("A31000").End(xlUp).Row Set myrng = Range(Cells(2, 1), Cells(endr, 1)) For Each chk In myrng If mymax(1) < chk.Value Then mymax(1) = chk.Value mymax(0) = chk.Row End If Next End Sub |
Sub シート関数3() Dim i As Integer, mymax(1) As Integer Dim mydat As Variant ThisWorkbook.Sheets("Sheet3").Select endr = Range("A31000").End(xlUp).Row mydat = Range(Cells(1, 1), Cells(endr, 1)) For i = 1 To endr If mymax(1) < mydat(i, 1) Then mymax(1) = mydat(i, 1) mymax(0) = i End If Next End Sub |
Sub シート関数4() Dim i As Integer, mymax As Integer Dim myrng As Range ThisWorkbook.Sheets("Sheet3").Select endr = Range("A31000").End(xlUp).Row Set myrng = Range(Cells(2, 1), Cells(endr, 1)) mymax = Application.WorksheetFunction.Max(myrng) End Sub |
Sub 文字型関数1() Dim i As Long For i = 1 To 300000 dd = Mid("VWAPチャート グラフ 65", 10) Next End Sub --------------------------------------------------------- Sub 文字型関数2() Dim i As Long For i = 1 To 300000 dd = Mid$("VWAPチャート グラフ 65", 10) Next End Sub |
Chr$ | ChrB$ | CurDir$ |
Date$ | Dir$ | Error$ |
Format$ | Hex$ | Input$ |
LCase$ | Left$ | LeftB$ |
LTrim$ | Mid$ | Oct$ |
Right$ | RightB$ | RTrim$ |
Space$ | Str$ | String$ |
Time$ | Trim$ | UCase$ |