シングルクォート削除

目次

コード


Sub シングルクォート削除処理()

On Error Resume Next
Selection.TextToColumns

'エラー表示
If Err.Number <> 0 Then
    MsgBox "エラー番号:" & Err.Number & vbCrLf & _
           "エラーの種類:" & Err.Description, vbExclamation
Else
    MsgBox Selection.Address & "範囲の処理完了", vbInformation
End If
On Error GoTo 0

End Sub

コード・全カラム対象


Sub シングルクォート削除処理繰り返し版()

On Error Resume Next

Dim myCol As Variant
Dim targetCol As Variant    '1列目から最終列までの範囲を格納(※スペシャルセルの最後のセルの列から取得)
Set targetCol = Range(Columns(1), Columns(Range("A1").SpecialCells(xlCellTypeLastCell).Column))

For Each myCol In targetCol
    myCol.Select
    '選択セルがすべて空白以外のとき実行
    If WorksheetFunction.CountBlank(Selection) <> Selection.Count Then
        Selection.TextToColumns
    End If
Next myCol

'エラー表示
If Err.Number <> 0 Then
    MsgBox "エラー番号:" & Err.Number & vbCrLf & _
           "エラーの種類:" & Err.Description, vbExclamation
Else
    MsgBox targetCol.Address & "範囲の処理完了", vbInformation
End If
On Error GoTo 0

End Sub

解説

エクセル機能の「区切り位置」(TextToColumns)を何も指定せずに実行するとシングルクォートを削除可能。ただし、複数列の処理は不可。
TextToColumnsを、シングルクォートのみセルで実行するとエラーになるため、全カラム版では、ワークシート関数の「countblank」*1と、「selection.count」*2が一致する場合は処理をスキップさせている。
*1:CountBlankは、シングルクォートのみセルも空白とみなす
*2:selection.countは、選択範囲のセルの個数を返す(セルの値によらない)
(参考)isEmpty関数は、シングルクォートのみセルも存在するとみなす