![]() |
CSVファイルを読み込む:Excel VBA入門 |
スポンサードリンク | |
Sub Sample0() Dim myFileName As Variant Dim Fcn As Long Dim i As Long Dim buf As String Dim tmp As Variant myFileName = Application.GetOpenFilename(FileFilter:="CSVファイル(*.csv),*.csv", _ Title:="CSVファイルの選択") If myFileName = False Then Exit Sub End If With Worksheets("Sheet1") Open myFileName For Input As #1 Do Until EOF(1) Line Input #1, buf Fcn = Fcn + 1 tmp = Split(buf, ",") '書き出し For i = LBound(tmp) To UBound(tmp) .Cells(Fcn + 1, i + 1).Value = tmp(i) Next i Loop Close #1 End With End Sub |
Sub Sample0a() Dim myFileName As Variant Dim Fcn As Long Dim i As Long Dim buf As String Dim tmp As Variant myFileName = Application.GetOpenFilename(FileFilter:="CSVファイル(*.csv),*.csv", _ Title:="CSVファイルの選択") If myFileName = False Then Exit Sub End If With Worksheets("Sheet1") Open myFileName For Input As #1 Do Until EOF(1) Line Input #1, buf Fcn = Fcn + 1 tmp = Split(buf, ",") '書き出し .Cells(Fcn + 1, 1).NumberFormatLocal = "@" .Cells(Fcn + 1, 1).Value = CStr(tmp(0)) .Cells(Fcn + 1, 2).NumberFormatLocal = "yyyy年m月d日" .Cells(Fcn + 1, 2).Value = DateValue(tmp(1)) For i = 2 To UBound(tmp) .Cells(Fcn + 1, i + 1).Value = tmp(i) Next i Loop Close #1 End With End Sub |
Sub Sample0b() Dim myFileName As Variant Dim Fcn As Long Dim i As Long Dim buf As String Dim tmp As Variant myFileName = Application.GetOpenFilename(FileFilter:="CSVファイル(*.csv),*.csv", _ Title:="CSVファイルの選択") If myFileName = False Then Exit Sub End If With Worksheets("Sheet1") Open myFileName For Input As #1 Do Until EOF(1) Line Input #1, buf Fcn = Fcn + 1 tmp = Split(buf, ",") '書き出し If Left(tmp(0), 1) = """" And Right(tmp(0), 1) = """" Then tmp(0) = Mid(tmp(0), 2, Len(tmp(0)) - 2) End If .Cells(Fcn + 1, 1).NumberFormatLocal = "@" .Cells(Fcn + 1, 1).Value = CStr(tmp(0)) .Cells(Fcn + 1, 2).NumberFormatLocal = "yyyy年m月d日" .Cells(Fcn + 1, 2).Value = DateValue(tmp(1)) For i = 2 To UBound(tmp) .Cells(Fcn + 1, i + 1).Value = tmp(i) Next i Loop Close #1 End With End Sub |
Sub Sample1() Dim myFileName As Variant Dim Fcn As Long Dim i As Long, j As Long Dim buf As String Dim tmp As Variant Dim tmp2() As Variant Dim cnt As Integer Dim myflag As Boolean myFileName = Application.GetOpenFilename(FileFilter:="CSVファイル(*.csv),*.csv", _ Title:="CSVファイルの選択") If myFileName = False Then Exit Sub End If With Worksheets("Sheet1") Open myFileName For Input As #1 Do Until EOF(1) Line Input #1, buf Fcn = Fcn + 1 tmp = Split(buf, ",") myflag = False cnt = 0 For i = LBound(tmp) To UBound(tmp) If myflag = False And Left(tmp(i), 1) = """" And Right(tmp(i), 1) = """" Then cnt = cnt + 1 ReDim Preserve tmp2(cnt) tmp2(cnt) = Mid(tmp(i), 2, Len(tmp(i)) - 2) ElseIf myflag = False And Left(tmp(i), 1) <> """" And Right(tmp(i), 1) <> """" Then cnt = cnt + 1 ReDim Preserve tmp2(cnt) tmp2(cnt) = tmp(i) ElseIf Left(tmp(i), 1) = """" And Right(tmp(i), 1) <> """" Then cnt = cnt + 1 ReDim Preserve tmp2(cnt) tmp2(cnt) = Mid(tmp(i), 2, Len(tmp(i))) myflag = True ElseIf myflag = True And Left(tmp(i), 1) <> """" And Right(tmp(i), 1) <> """" Then tmp2(cnt) = tmp2(cnt) & tmp(i) ElseIf myflag = True And Left(tmp(i), 1) <> """" And Right(tmp(i), 1) = """" Then tmp2(cnt) = tmp2(cnt) & Left(tmp(i), Len(tmp(i)) - 1) myflag = False End If Next i '書き出し For i = 1 To UBound(tmp2) .Cells(Fcn + 1, i).Value = tmp2(i) Next i Loop Close #1 End With End Sub |
スポンサードリンク
PageViewCounter
Since2006/2/27