What I would like to see in Excel 2016

Actually remembered I did email it to someone so....

Code:
Public gstr_Wbk_Name As String
  
  ' Comments  : Code Indenter
  '
  ' REQUIRED REFERENCE : Microsoft Visual Basic for Applications Extensibility 5.3
  '
  ' Date        Change
  ' ------------------------------------------------
  ' 16-May-13 Created
  ' 16-Jun-16 Fix up handling of "IF *** THEN"
  ' 16-Feb-19 Modified to work for me, source: "http://www.mrexcel.com/forum/excel-questions/802527-replicate-indentervba-exe-com-add.html"
  
  
Sub MyCodeIndenter()
  
  Dim iLoop As Long
  Dim arListOfCodeModules() As String
  Dim vbComp As VBIDE.VBComponent
  
  gstr_Wbk_Name = ActiveWorkbook.Name
  
  If Len(gstr_Wbk_Name) > 0 Then
    
    ReDim arListOfCodeModules(1 To 500)
    For Each vbComp In Application.Workbooks(gstr_Wbk_Name).VBProject.VBComponents
      If vbComp.CodeModule.CountOfLines > 3 Then
        iLoop = iLoop + 1
        arListOfCodeModules(iLoop) = vbComp.Name
      End If
    Next vbComp
    Set vbComp = Nothing
    
    If iLoop > 0 Then
      ReDim Preserve arListOfCodeModules(1 To iLoop)
      For iLoop = LBound(arListOfCodeModules) To UBound(arListOfCodeModules)
        Call IndentModule(NameOfModule:=arListOfCodeModules(iLoop))
      Next iLoop
    End If
    Erase arListOfCodeModules
    
    MsgBox prompt:="Done", Buttons:=vbExclamation, Title:="VBA Code Indented for file " & gstr_Wbk_Name
    
  End If
  
End Sub
  
Private Sub IndentModule(ByVal NameOfModule As String)
  
  On Error Resume Next
  
  Const IndentStep As Long = 2
  
  Dim blnInitialCommentInModule As Boolean
  Dim blnIndentNextLine As Boolean, blnOutdentNow As Boolean
  Dim blnNoIndent As Boolean
  
  Dim iLoop As Long, HowManyIndents As Long
  Dim strMyCodeLine As String
  Dim vbComp As VBIDE.VBComponent
  Dim vbProj As VBIDE.VBProject
  
  Set vbProj = Workbooks(gstr_Wbk_Name).VBProject
  Set vbComp = vbProj.VBComponents(NameOfModule)
  
  With vbComp.CodeModule
    
    blnNoIndent = False
    blnInitialCommentInModule = True
    blnIndentNextLine = False
    blnOutdentNow = False
    
    For iLoop = 1 To .CountOfLines
      
      strMyCodeLine = Trim$(.Lines(iLoop, 1))
      
      If Len(strMyCodeLine) > 0 Then
        
        Select Case FirstWord(strMyCodeLine)
          
        Case "Option"
          blnNoIndent = True
          
        Case "Declare", "Enum", "Function", "Private", "Public", "Sub", "Type"
          blnNoIndent = True
          blnInitialCommentInModule = False
          
        Case "If", "IIf"
          blnIndentNextLine = True
          If InStr(strMyCodeLine, " Then ") > 0 Then
          If Not Replace$(strMyCodeLine, " ", vbNullString) Like "*Then'*" Then blnIndentNextLine = False
          End If
          blnInitialCommentInModule = False
          
        Case "Do", "For", "Select", "With"
          blnIndentNextLine = True
          blnInitialCommentInModule = False
          
        Case "Case"
          'if PREVIOUS line was not a Select or Case statement, outdent now
          If Len(.Lines(iLoop - 1, 1)) > 0 Then
            If Not FirstWord(Trim$(.Lines(iLoop - 1, 1))) Like "Case" And Not FirstWord(Trim$(.Lines(iLoop - 1, 1))) Like "Select" Then
              blnOutdentNow = True
            End If
          End If
          'if NEXT line is not an End or Case statement, indent next line
          If Len(.Lines(iLoop + 1, 1)) > 0 Then
            If Not FirstWord(Trim$(.Lines(iLoop + 1, 1))) Like "End" And Not FirstWord(Trim$(.Lines(iLoop + 1, 1))) Like "Case" Then
              blnIndentNextLine = True
            End If
          End If
          
        Case "Else", "ElseIf"
          blnOutdentNow = True
          blnIndentNextLine = True
          blnInitialCommentInModule = False
          
        Case "End"
          If strMyCodeLine Like "End Function*" Or strMyCodeLine Like "End Sub*" Then
            blnNoIndent = True
          End If
          If strMyCodeLine Like "End If*" Or strMyCodeLine Like "End Select*" Or strMyCodeLine Like "End With*" Then
            blnOutdentNow = True
          End If
          blnInitialCommentInModule = False
          
        Case "Loop", "Next"
          blnOutdentNow = True
          blnInitialCommentInModule = False
          
        Case Else
          If FirstWord(strMyCodeLine) Like "*:" Then
            blnNoIndent = True
          End If
          
        End Select
        
      End If
      
      If blnNoIndent Then HowManyIndents = 0
      If blnOutdentNow Then HowManyIndents = HowManyIndents - 1
      
      .ReplaceLine iLoop, String(HowManyIndents * IndentStep, "  ") & strMyCodeLine
      
      If HowManyIndents = 0 Then HowManyIndents = 1
      If blnInitialCommentInModule Then HowManyIndents = 0
      If blnIndentNextLine Then HowManyIndents = HowManyIndents + 1
      
      blnNoIndent = False
      blnIndentNextLine = False
      blnOutdentNow = False
      
    Next iLoop
    
  End With
  
  Set vbComp = Nothing
  Set vbProj = Nothing
  
End Sub
  
Private Function FirstWord(ByVal WholeLine As String) As String
  
  Dim ar As Variant
  ar = Split(WholeLine, " ")
  FirstWord = ar(LBound(ar))
  Erase ar
  
End Function
Obviously make sure that you set the reference.
 

Excel Facts

Difference between two dates
Secret function! Use =DATEDIF(A2,B2,"Y")&" years"&=DATEDIF(A2,B2,"YM")&" months"&=DATEDIF(A2,B2,"MD")&" days"
posting a newer version of that code indenter as just the other day I revised it.

now has
- optional line numbers
- whether line numbers are unique in a workbook or just reset every procedure
- whether or not line numbers are used for comments, or blank lines

you can see the variables that control these. I just hard coded some settings as I almost never change them

still uses a userform to select the workbook to process. I think if you don't want that the changes are very simple. gsWbkName just needs the name of the file

cheers

Code:
Option Explicit


' Comments  : Code Indenter
'
' REQUIRED REFERENCE : Microsoft Visual Basic for Applications Extensibility 5.3
'
' Date    Change
' ------------------------------------------------------------------------------
' 16-May-13 Created
' 16-Jun-15 Fix handling of "IF *** THEN" lines
' 13-Mar-17 Quick hack to tidy up long spaces before comments. Add "End Enum"
' 07-Apr-17 Add Yes/No option to line number code
' 12-Apr-17 Optionally allow line numbers to be unique within a workbook


Public gsWbkName As String


Const mbUNIQUE_LINE_NUMBERS As Boolean = True 'When line numbers are used, uniquer line numbers are different for every code line in the file (otherwise restart numbering every routine/function)
Dim mlLineNumber As Long
    
Sub IndentCode()
101
102     Dim bWantLineNumbers As Boolean
103     Dim iLoop As Long
104     Dim asListOfCodeModules() As String
105     Dim vbComp As VBIDE.VBComponent
106
107     ufWorkbooks.Show
108
109     If Len(gsWbkName) > 0 Then
110
111         If MsgBox(Prompt:="Do you want code line numbers?", Buttons:=vbYesNo + vbDefaultButton1, Title:="Code Line Numbers?") = vbYes Then
112             bWantLineNumbers = True
113             mlLineNumber = 0 'Zero value used in IndentModule code to know it is first time through loop. (And need to initialise line numbering)
114         End If
115
116         ReDim asListOfCodeModules(1 To 500)
117         For Each vbComp In Application.Workbooks(gsWbkName).VBProject.VBComponents
118             If vbComp.CodeModule.CountOfLines > 3 Then
119                 iLoop = iLoop + 1
120                 asListOfCodeModules(iLoop) = vbComp.Name
121             End If
122         Next vbComp
123         Set vbComp = Nothing
124
125         If iLoop > 0 Then
126             ReDim Preserve asListOfCodeModules(1 To iLoop)
127             For iLoop = LBound(asListOfCodeModules) To UBound(asListOfCodeModules)
128                 Call IndentModule(sNameOfModule:=asListOfCodeModules(iLoop), bWantLineNumbers:=bWantLineNumbers)
129             Next iLoop
130         End If
131         Erase asListOfCodeModules
132
133         MsgBox Prompt:="Done", Buttons:=vbExclamation, Title:="VBA Code Indented for file " & gsWbkName
134
135     End If
136
End Sub


Private Sub IndentModule(ByRef sNameOfModule As String, ByRef bWantLineNumbers As Boolean)
137
138     Const bWANT_LINE_NUMBERS_FOR_BLANK_LINES As Boolean = True 'When line numbers are used, whether applied to blank lines
139     Const bWANT_LINE_NUMBERS_FOR_COMMENTS As Boolean = True 'When line numbers are used, whether applied to comments
140
141     Const lINDENT_STEP As Long = 4 'Indent size (spaces)
142
143     Const lLINE_NUMBER_FIRST As Long = 10000 'For small projects, lower value may be preferred. Such as 100 or 1000
144     Const lLINE_NUMBER_INCREMENT As Long = 1
145
146     Dim bContinuingLine As Boolean
147     Dim bGetsLineNumber As Boolean
148     Dim bIncase As Boolean
149     Dim bIndentNextLine As Boolean, bOutdentNow As Boolean
150     Dim bInitialCommentInModule As Boolean
151     Dim bInProcedure As Boolean
152     Dim bInSelect As Boolean
153     Dim bIsComment As Boolean
154     Dim bNoIndent As Boolean
155     Dim bSelectCaseCannotHaveLineNumbersBeforeFirstCase As Boolean
156     Dim bSelectCaseJustStarted As Boolean
157
158     Dim lLenBefore As Long, lLenAfter As Long
159     Dim iLoop As Long, lHowManyIndents As Long
160     Dim sMyCodeLine As String
161     Dim sNewLine As String
162
163     Dim vbComp As VBIDE.VBComponent
164     Dim vbProj As VBIDE.VBProject
165     '-------------------------
166     Set vbProj = Workbooks(gsWbkName).VBProject
167     Set vbComp = vbProj.VBComponents(sNameOfModule)
168     With vbComp.CodeModule
169
170         bContinuingLine = False
171         bNoIndent = False
172         bInitialCommentInModule = True
173         bIndentNextLine = False
174         bInProcedure = False
175         bIncase = False
176         bOutdentNow = False
177         bSelectCaseJustStarted = False
178         If mbUNIQUE_LINE_NUMBERS Then
179             If mlLineNumber = 0 Then mlLineNumber = lLINE_NUMBER_FIRST
180         Else 'Reset line number each time routine called
181             mlLineNumber = lLINE_NUMBER_FIRST
182         End If
183
184         For iLoop = 1 To .CountOfLines
185
186             sMyCodeLine = Trim$(.Lines(iLoop, 1))
187
188             '=================================================================
189             '13-Mar-17 Quick hack to tidy up long spaces before comments
190             sMyCodeLine = Replace$(sMyCodeLine, "'", "'")        'first pass
191             lLenBefore = Len(sMyCodeLine)
192             sMyCodeLine = Replace$(sMyCodeLine, "'", "'")
193             lLenAfter = Len(sMyCodeLine)
194             Do While lLenAfter <> lLenBefore
195                 lLenBefore = lLenAfter
196                 sMyCodeLine = Replace$(sMyCodeLine, "'", "'")
197                 lLenAfter = Len(sMyCodeLine)
198             Loop
199             '=================================================================
200             '=================================================================
201             '07-Apr-17 Quick code to remove pre-existing line numbers
202             Do While Left$(sMyCodeLine, 1) Like "[0-9]"
203                 sMyCodeLine = Trim$(Right$(sMyCodeLine, Len(sMyCodeLine) - 1))
204             Loop
205             '=================================================================
206             bGetsLineNumber = True
207
208             If Len(sMyCodeLine) > 0 Then
209
210                 bIsComment = Left$(sMyCodeLine, 1) = "'"
211
212                 Select Case FirstWord(sMyCodeLine)
                        
                        Case "Option"
213                         bGetsLineNumber = False
214                         bNoIndent = True
215
216                     Case "Declare", "Enum", "Function", "Private", "Public", "Sub", "Type"
217                         bGetsLineNumber = False
218                         bNoIndent = True
219                         bInitialCommentInModule = False
220
221                     Case "If", "IIf"
222                         'For IF lines, default to indent the next line. However check for something after the THEN.
223                         bIndentNextLine = True
224                         'If the next non-space character is NOT "'" (so, it is not a comment) then do not indent the
225                         'next line as it is a one line IF THEN: not the common IF THEN - END IF block. Clear as mud?
226                         If InStr(sMyCodeLine, " Then ") > 0 Then
227                         If Not Replace$(sMyCodeLine, " ", vbNullString) Like "*Then'*" Then bIndentNextLine = False
228                         End If
229                         bInitialCommentInModule = False
230
231                     Case "Do", "For", "With"
232                         bIndentNextLine = True
233                         bInitialCommentInModule = False
234
235                     Case "Select"
236                         bIndentNextLine = True
237                         bInitialCommentInModule = False
238                         bSelectCaseJustStarted = True
239
240                     Case "Case"
241                         bIndentNextLine = True
242                         If bIncase Then bOutdentNow = True
243                         bIncase = True
244
245                     Case "Else", "ElseIf"
246                         bOutdentNow = True
247                         bIndentNextLine = True
248                         bInitialCommentInModule = False
249
250                     Case "End"
251                         If sMyCodeLine Like "End Enum*" Then
252                             bGetsLineNumber = False
253                             bNoIndent = True
254                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
255                         End If
256                         If sMyCodeLine Like "End Function*" Or sMyCodeLine Like "End Sub*" Then
257                             bInProcedure = False
258                             bGetsLineNumber = False
259                             bNoIndent = True
260                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
261                         End If
262                         If sMyCodeLine Like "End If*" Or sMyCodeLine Like "End Select*" Or sMyCodeLine Like "End With*" Then
263                             bOutdentNow = True
264                             bInitialCommentInModule = False
265                         End If
266                         If sMyCodeLine Like "End Select*" Then
267                             bIncase = False
268                         End If
269
270                     Case "Loop", "Next"
271                         bOutdentNow = True
272                         bInitialCommentInModule = False
273
274                     Case Else
275                         If FirstWord(sWholeLine:=sMyCodeLine) Like "*:" Then
276                             bGetsLineNumber = False
277                             bNoIndent = True
278                         End If
279
280                 End Select
281
282             End If
283
284             If bNoIndent Then lHowManyIndents = 0
285             If bOutdentNow Then lHowManyIndents = lHowManyIndents - 1
286             If sMyCodeLine Like "End Select*" Then lHowManyIndents = lHowManyIndents - 1
287             '------------------------------
288             'Last step before new line creation: handle line numbering.
289             If bWantLineNumbers And bInProcedure And bGetsLineNumber Then    ' If want line number at all
290
291                 If bContinuingLine Or (bIsComment And Not bWANT_LINE_NUMBERS_FOR_COMMENTS) Or bSelectCaseCannotHaveLineNumbersBeforeFirstCase Then
292                     'These are special, replace the line number with spaces instead: keeps alignment with other lines.
293                     sNewLine = String(Len(CStr(mlLineNumber)), " ") & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
294                 Else
295                     If bWANT_LINE_NUMBERS_FOR_BLANK_LINES Or Len(sMyCodeLine) > 0 Then  'Want to number blank lines as well as normal lines
296                         mlLineNumber = mlLineNumber + lLINE_NUMBER_INCREMENT
297                         sNewLine = CStr(mlLineNumber) & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
298                     Else    'don't number blank lines
299                         sNewLine = ""
300                     End If
301                 End If
302
303             Else    'No line numbers
304                 sNewLine = String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
305             End If
306             .ReplaceLine iLoop, sNewLine
307
308             If sMyCodeLine Like "Private Function *" Or sMyCodeLine Like "Public Function *" _
                    Or sMyCodeLine Like "Function *" Or sMyCodeLine Like "Private Sub *" _
                    Or sMyCodeLine Like "Public Sub *" Or sMyCodeLine Like "Sub *" Then
309                 bInProcedure = True
310                 If Not mbUNIQUE_LINE_NUMBERS Then mlLineNumber = lLINE_NUMBER_FIRST
311             End If
312             '------------------------------
313             If lHowManyIndents = 0 Then lHowManyIndents = 1
314             If bInitialCommentInModule Then lHowManyIndents = 0
315             If bIndentNextLine Then lHowManyIndents = lHowManyIndents + 1
316
317             bContinuingLine = Right$(sMyCodeLine, 1) = "_"
318             bNoIndent = False
319             bIndentNextLine = False
320             bOutdentNow = False
321
322             'At end of code so is after line number handling of "Select Case"
323             If bSelectCaseJustStarted Then
324                 bSelectCaseJustStarted = False 'It is turned off within the same loop as turned on
325                 bSelectCaseCannotHaveLineNumbersBeforeFirstCase = True 'Available for use next time through loop
326             End If
327             If bIncase Then bSelectCaseCannotHaveLineNumbersBeforeFirstCase = False 'Now the first case is reached, turn off
328
329         Next iLoop
330     End With
331
332     Set vbComp = Nothing
333     Set vbProj = Nothing
334
End Sub


Private Function FirstWord(ByRef sWholeLine As String) As String 'NOTE : input is trimmed before calling this function
335
336     Dim ar As Variant
337
338     ar = Split(sWholeLine, " ")
339     FirstWord = ar(LBound(ar))
340     Erase ar
341
End Function
 
Fazza

Are you still on Excel 2003 as your location informs?
 
Fazza

Are you still on Excel 2003 as your location informs?
No. (Unfortunately :))
At work I use a recent version, at home the desktop has 2007. My old laptop has Excel 2003 - though I use it rarely these days. Even in the newer versions I prefer to save files in .xls format; though lately have used some xlsb. Most of the day to day files I use are actually from Excel 2003: and I normally just use Excel 2003 formats (colorindex up to 55). Newer versions offer very little new features of interest to me: I use the Excel 2003 shortcuts and most days (I use Excel most of the day) don't touch the ribbon. Maybe just for an occassional page setup. cheers
 
And thank you FAZZA for the update! (would you be able to post the Userform code as well, pretty please?)

Like I said before, it has been a long while since I have spent much time on this board, but dang it is is still as good as it ever was. Such a great place!! :)



posting a newer version of that code indenter as just the other day I revised it.

now has
- optional line numbers
- whether line numbers are unique in a workbook or just reset every procedure
- whether or not line numbers are used for comments, or blank lines

you can see the variables that control these. I just hard coded some settings as I almost never change them

still uses a userform to select the workbook to process. I think if you don't want that the changes are very simple. gsWbkName just needs the name of the file

cheers

Code:
Option Explicit


' Comments  : Code Indenter
'
' REQUIRED REFERENCE : Microsoft Visual Basic for Applications Extensibility 5.3
'
' Date    Change
' ------------------------------------------------------------------------------
' 16-May-13 Created
' 16-Jun-15 Fix handling of "IF *** THEN" lines
' 13-Mar-17 Quick hack to tidy up long spaces before comments. Add "End Enum"
' 07-Apr-17 Add Yes/No option to line number code
' 12-Apr-17 Optionally allow line numbers to be unique within a workbook


Public gsWbkName As String


Const mbUNIQUE_LINE_NUMBERS As Boolean = True 'When line numbers are used, uniquer line numbers are different for every code line in the file (otherwise restart numbering every routine/function)
Dim mlLineNumber As Long
    
Sub IndentCode()
101
102     Dim bWantLineNumbers As Boolean
103     Dim iLoop As Long
104     Dim asListOfCodeModules() As String
105     Dim vbComp As VBIDE.VBComponent
106
107     ufWorkbooks.Show
108
109     If Len(gsWbkName) > 0 Then
110
111         If MsgBox(Prompt:="Do you want code line numbers?", Buttons:=vbYesNo + vbDefaultButton1, Title:="Code Line Numbers?") = vbYes Then
112             bWantLineNumbers = True
113             mlLineNumber = 0 'Zero value used in IndentModule code to know it is first time through loop. (And need to initialise line numbering)
114         End If
115
116         ReDim asListOfCodeModules(1 To 500)
117         For Each vbComp In Application.Workbooks(gsWbkName).VBProject.VBComponents
118             If vbComp.CodeModule.CountOfLines > 3 Then
119                 iLoop = iLoop + 1
120                 asListOfCodeModules(iLoop) = vbComp.Name
121             End If
122         Next vbComp
123         Set vbComp = Nothing
124
125         If iLoop > 0 Then
126             ReDim Preserve asListOfCodeModules(1 To iLoop)
127             For iLoop = LBound(asListOfCodeModules) To UBound(asListOfCodeModules)
128                 Call IndentModule(sNameOfModule:=asListOfCodeModules(iLoop), bWantLineNumbers:=bWantLineNumbers)
129             Next iLoop
130         End If
131         Erase asListOfCodeModules
132
133         MsgBox Prompt:="Done", Buttons:=vbExclamation, Title:="VBA Code Indented for file " & gsWbkName
134
135     End If
136
End Sub


Private Sub IndentModule(ByRef sNameOfModule As String, ByRef bWantLineNumbers As Boolean)
137
138     Const bWANT_LINE_NUMBERS_FOR_BLANK_LINES As Boolean = True 'When line numbers are used, whether applied to blank lines
139     Const bWANT_LINE_NUMBERS_FOR_COMMENTS As Boolean = True 'When line numbers are used, whether applied to comments
140
141     Const lINDENT_STEP As Long = 4 'Indent size (spaces)
142
143     Const lLINE_NUMBER_FIRST As Long = 10000 'For small projects, lower value may be preferred. Such as 100 or 1000
144     Const lLINE_NUMBER_INCREMENT As Long = 1
145
146     Dim bContinuingLine As Boolean
147     Dim bGetsLineNumber As Boolean
148     Dim bIncase As Boolean
149     Dim bIndentNextLine As Boolean, bOutdentNow As Boolean
150     Dim bInitialCommentInModule As Boolean
151     Dim bInProcedure As Boolean
152     Dim bInSelect As Boolean
153     Dim bIsComment As Boolean
154     Dim bNoIndent As Boolean
155     Dim bSelectCaseCannotHaveLineNumbersBeforeFirstCase As Boolean
156     Dim bSelectCaseJustStarted As Boolean
157
158     Dim lLenBefore As Long, lLenAfter As Long
159     Dim iLoop As Long, lHowManyIndents As Long
160     Dim sMyCodeLine As String
161     Dim sNewLine As String
162
163     Dim vbComp As VBIDE.VBComponent
164     Dim vbProj As VBIDE.VBProject
165     '-------------------------
166     Set vbProj = Workbooks(gsWbkName).VBProject
167     Set vbComp = vbProj.VBComponents(sNameOfModule)
168     With vbComp.CodeModule
169
170         bContinuingLine = False
171         bNoIndent = False
172         bInitialCommentInModule = True
173         bIndentNextLine = False
174         bInProcedure = False
175         bIncase = False
176         bOutdentNow = False
177         bSelectCaseJustStarted = False
178         If mbUNIQUE_LINE_NUMBERS Then
179             If mlLineNumber = 0 Then mlLineNumber = lLINE_NUMBER_FIRST
180         Else 'Reset line number each time routine called
181             mlLineNumber = lLINE_NUMBER_FIRST
182         End If
183
184         For iLoop = 1 To .CountOfLines
185
186             sMyCodeLine = Trim$(.Lines(iLoop, 1))
187
188             '=================================================================
189             '13-Mar-17 Quick hack to tidy up long spaces before comments
190             sMyCodeLine = Replace$(sMyCodeLine, "'", "'")        'first pass
191             lLenBefore = Len(sMyCodeLine)
192             sMyCodeLine = Replace$(sMyCodeLine, "'", "'")
193             lLenAfter = Len(sMyCodeLine)
194             Do While lLenAfter <> lLenBefore
195                 lLenBefore = lLenAfter
196                 sMyCodeLine = Replace$(sMyCodeLine, "'", "'")
197                 lLenAfter = Len(sMyCodeLine)
198             Loop
199             '=================================================================
200             '=================================================================
201             '07-Apr-17 Quick code to remove pre-existing line numbers
202             Do While Left$(sMyCodeLine, 1) Like "[0-9]"
203                 sMyCodeLine = Trim$(Right$(sMyCodeLine, Len(sMyCodeLine) - 1))
204             Loop
205             '=================================================================
206             bGetsLineNumber = True
207
208             If Len(sMyCodeLine) > 0 Then
209
210                 bIsComment = Left$(sMyCodeLine, 1) = "'"
211
212                 Select Case FirstWord(sMyCodeLine)
                        
                        Case "Option"
213                         bGetsLineNumber = False
214                         bNoIndent = True
215
216                     Case "Declare", "Enum", "Function", "Private", "Public", "Sub", "Type"
217                         bGetsLineNumber = False
218                         bNoIndent = True
219                         bInitialCommentInModule = False
220
221                     Case "If", "IIf"
222                         'For IF lines, default to indent the next line. However check for something after the THEN.
223                         bIndentNextLine = True
224                         'If the next non-space character is NOT "'" (so, it is not a comment) then do not indent the
225                         'next line as it is a one line IF THEN: not the common IF THEN - END IF block. Clear as mud?
226                         If InStr(sMyCodeLine, " Then ") > 0 Then
227                         If Not Replace$(sMyCodeLine, " ", vbNullString) Like "*Then'*" Then bIndentNextLine = False
228                         End If
229                         bInitialCommentInModule = False
230
231                     Case "Do", "For", "With"
232                         bIndentNextLine = True
233                         bInitialCommentInModule = False
234
235                     Case "Select"
236                         bIndentNextLine = True
237                         bInitialCommentInModule = False
238                         bSelectCaseJustStarted = True
239
240                     Case "Case"
241                         bIndentNextLine = True
242                         If bIncase Then bOutdentNow = True
243                         bIncase = True
244
245                     Case "Else", "ElseIf"
246                         bOutdentNow = True
247                         bIndentNextLine = True
248                         bInitialCommentInModule = False
249
250                     Case "End"
251                         If sMyCodeLine Like "End Enum*" Then
252                             bGetsLineNumber = False
253                             bNoIndent = True
254                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
255                         End If
256                         If sMyCodeLine Like "End Function*" Or sMyCodeLine Like "End Sub*" Then
257                             bInProcedure = False
258                             bGetsLineNumber = False
259                             bNoIndent = True
260                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
261                         End If
262                         If sMyCodeLine Like "End If*" Or sMyCodeLine Like "End Select*" Or sMyCodeLine Like "End With*" Then
263                             bOutdentNow = True
264                             bInitialCommentInModule = False
265                         End If
266                         If sMyCodeLine Like "End Select*" Then
267                             bIncase = False
268                         End If
269
270                     Case "Loop", "Next"
271                         bOutdentNow = True
272                         bInitialCommentInModule = False
273
274                     Case Else
275                         If FirstWord(sWholeLine:=sMyCodeLine) Like "*:" Then
276                             bGetsLineNumber = False
277                             bNoIndent = True
278                         End If
279
280                 End Select
281
282             End If
283
284             If bNoIndent Then lHowManyIndents = 0
285             If bOutdentNow Then lHowManyIndents = lHowManyIndents - 1
286             If sMyCodeLine Like "End Select*" Then lHowManyIndents = lHowManyIndents - 1
287             '------------------------------
288             'Last step before new line creation: handle line numbering.
289             If bWantLineNumbers And bInProcedure And bGetsLineNumber Then    ' If want line number at all
290
291                 If bContinuingLine Or (bIsComment And Not bWANT_LINE_NUMBERS_FOR_COMMENTS) Or bSelectCaseCannotHaveLineNumbersBeforeFirstCase Then
292                     'These are special, replace the line number with spaces instead: keeps alignment with other lines.
293                     sNewLine = String(Len(CStr(mlLineNumber)), " ") & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
294                 Else
295                     If bWANT_LINE_NUMBERS_FOR_BLANK_LINES Or Len(sMyCodeLine) > 0 Then  'Want to number blank lines as well as normal lines
296                         mlLineNumber = mlLineNumber + lLINE_NUMBER_INCREMENT
297                         sNewLine = CStr(mlLineNumber) & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
298                     Else    'don't number blank lines
299                         sNewLine = ""
300                     End If
301                 End If
302
303             Else    'No line numbers
304                 sNewLine = String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
305             End If
306             .ReplaceLine iLoop, sNewLine
307
308             If sMyCodeLine Like "Private Function *" Or sMyCodeLine Like "Public Function *" _
                    Or sMyCodeLine Like "Function *" Or sMyCodeLine Like "Private Sub *" _
                    Or sMyCodeLine Like "Public Sub *" Or sMyCodeLine Like "Sub *" Then
309                 bInProcedure = True
310                 If Not mbUNIQUE_LINE_NUMBERS Then mlLineNumber = lLINE_NUMBER_FIRST
311             End If
312             '------------------------------
313             If lHowManyIndents = 0 Then lHowManyIndents = 1
314             If bInitialCommentInModule Then lHowManyIndents = 0
315             If bIndentNextLine Then lHowManyIndents = lHowManyIndents + 1
316
317             bContinuingLine = Right$(sMyCodeLine, 1) = "_"
318             bNoIndent = False
319             bIndentNextLine = False
320             bOutdentNow = False
321
322             'At end of code so is after line number handling of "Select Case"
323             If bSelectCaseJustStarted Then
324                 bSelectCaseJustStarted = False 'It is turned off within the same loop as turned on
325                 bSelectCaseCannotHaveLineNumbersBeforeFirstCase = True 'Available for use next time through loop
326             End If
327             If bIncase Then bSelectCaseCannotHaveLineNumbersBeforeFirstCase = False 'Now the first case is reached, turn off
328
329         Next iLoop
330     End With
331
332     Set vbComp = Nothing
333     Set vbProj = Nothing
334
End Sub


Private Function FirstWord(ByRef sWholeLine As String) As String 'NOTE : input is trimmed before calling this function
335
336     Dim ar As Variant
337
338     ar = Split(sWholeLine, " ")
339     FirstWord = ar(LBound(ar))
340     Erase ar
341
End Function
 
sure, mate, cheers
Code:
Option Explicit


Private Sub btnCANCEL_Click()
  gsWbkName = vbNullString
  Unload ufWorkbooks
End Sub


Private Sub btnOK_Click()
  gsWbkName = vbNullString
  On Error Resume Next
  gsWbkName = lbWorkbooks.Value
  Unload ufWorkbooks
End Sub


Private Sub lbWorkbooks_DblClick(ByVal Cancel As MSForms.ReturnBoolean)
  gsWbkName = lbWorkbooks.Value
  Unload ufWorkbooks
End Sub


Private Sub UserForm_Initialize()


  Dim wbkLoop As Excel.Workbook


  For Each wbkLoop In Application.Workbooks
    Select Case wbkLoop.Name
      Case ThisWorkbook.Name, "PERSONAL.XLS", "PERSONAL.XLSB"
      Case Else: ufWorkbooks.lbWorkbooks.AddItem wbkLoop.Name
    End Select
  Next wbkLoop
  Set wbkLoop = Nothing


End Sub
 
I just noticed an error in the code indenter that I posted earlier.

What I posted has a useless section of code in lines 188 to 199. It doesn't do anything. It is supposed to remove large spaces and when the code ran on a copy of itself, it deleted the excess spaces & made the code useless. :) Using the code posted earlier will have no errors, it just won't remove excess spaces - which doesn't matter much.

Still, to fix it, here are the replacement lines 188 to 199.
Code:
188             '=================================================================
189             '13-Mar-17 Quick hack to tidy up long spaces before comments
190             sMyCodeLine = Replace$(sMyCodeLine, "    '", "'")        'first pass
191             lLenBefore = Len(sMyCodeLine)
192             sMyCodeLine = Replace$(sMyCodeLine, "  '", "'")
193             lLenAfter = Len(sMyCodeLine)
194             Do While lLenAfter <> lLenBefore
195                 lLenBefore = lLenAfter
196                 sMyCodeLine = Replace$(sMyCodeLine, "  '", "'")
197                 lLenAfter = Len(sMyCodeLine)
198             Loop
199             '=================================================================
And for completeness, the full corrected code.
Code:
Option Explicit


' Comments  : Code Indenter
'
' REQUIRED REFERENCE : Microsoft Visual Basic for Applications Extensibility 5.3
'
' Date    Change
' ------------------------------------------------------------------------------
' 16-May-13 Created
' 16-Jun-15 Fix handling of "IF *** THEN" lines
' 13-Mar-17 Quick hack to tidy up long spaces before comments. Add "End Enum"
' 07-Apr-17 Add Yes/No option to line number code
' 12-Apr-17 Optionally allow line numbers to be unique within a workbook


Public gsWbkName As String


Const mbUNIQUE_LINE_NUMBERS As Boolean = True 'When line numbers are used, uniquer line numbers are different for every code line in the file (otherwise restart numbering every routine/function)
Dim mlLineNumber As Long
    
Sub IndentCode()
101
102     Dim bWantLineNumbers As Boolean
103     Dim iLoop As Long
104     Dim asListOfCodeModules() As String
105     Dim vbComp As VBIDE.VBComponent
106
107     ufWorkbooks.Show
108
109     If Len(gsWbkName) > 0 Then
110
111         If MsgBox(Prompt:="Do you want code line numbers?", Buttons:=vbYesNo + vbDefaultButton1, Title:="Code Line Numbers?") = vbYes Then
112             bWantLineNumbers = True
113             mlLineNumber = 0 'Zero value used in IndentModule sub to know it is first time through loop. (And need to initialise line numbering)
114         End If
115
116         ReDim asListOfCodeModules(1 To 500)
117         For Each vbComp In Application.Workbooks(gsWbkName).VBProject.VBComponents
118             If vbComp.CodeModule.CountOfLines > 3 Then
119                 iLoop = iLoop + 1
120                 asListOfCodeModules(iLoop) = vbComp.Name
121             End If
122         Next vbComp
123         Set vbComp = Nothing
124
125         If iLoop > 0 Then
126             ReDim Preserve asListOfCodeModules(1 To iLoop)
127             For iLoop = LBound(asListOfCodeModules) To UBound(asListOfCodeModules)
128                 Call IndentModule(sNameOfModule:=asListOfCodeModules(iLoop), bWantLineNumbers:=bWantLineNumbers)
129             Next iLoop
130         End If
131         Erase asListOfCodeModules
132
133         MsgBox Prompt:="Done", Buttons:=vbExclamation, Title:="VBA Code Indented for file " & gsWbkName
134
135     End If
136
End Sub


Private Sub IndentModule(ByRef sNameOfModule As String, ByRef bWantLineNumbers As Boolean)
137
138     Const bWANT_LINE_NUMBERS_FOR_BLANK_LINES As Boolean = True 'When line numbers are used, whether applied to blank lines
139     Const bWANT_LINE_NUMBERS_FOR_COMMENTS As Boolean = True 'When line numbers are used, whether applied to comments
140
141     Const lINDENT_STEP As Long = 2 'Indent size (spaces)
142
143     Const lLINE_NUMBER_FIRST As Long = 100 'Say 100 for small projects or 10000 for large projects
144     Const lLINE_NUMBER_INCREMENT As Long = 1
145
146     Dim bContinuingLine As Boolean
147     Dim bGetsLineNumber As Boolean
148     Dim bIncase As Boolean
149     Dim bIndentNextLine As Boolean, bOutdentNow As Boolean
150     Dim bInitialCommentInModule As Boolean
151     Dim bInProcedure As Boolean
152     Dim bInSelect As Boolean
153     Dim bIsComment As Boolean
154     Dim bNoIndent As Boolean
155     Dim bSelectCaseCannotHaveLineNumbersBeforeFirstCase As Boolean
156     Dim bSelectCaseJustStarted As Boolean
157
158     Dim lLenBefore As Long, lLenAfter As Long
159     Dim iLoop As Long, lHowManyIndents As Long
160     Dim sMyCodeLine As String
161     Dim sNewLine As String
162
163     Dim vbComp As VBIDE.VBComponent
164     Dim vbProj As VBIDE.VBProject
165     '-------------------------
166     Set vbProj = Workbooks(gsWbkName).VBProject
167     Set vbComp = vbProj.VBComponents(sNameOfModule)
168     With vbComp.CodeModule
169
170         bContinuingLine = False
171         bNoIndent = False
172         bInitialCommentInModule = True
173         bIndentNextLine = False
174         bInProcedure = False
175         bIncase = False
176         bOutdentNow = False
177         bSelectCaseJustStarted = False
178         If mbUNIQUE_LINE_NUMBERS Then
179             If mlLineNumber = 0 Then mlLineNumber = lLINE_NUMBER_FIRST
180         Else 'Reset line number each time routine called
181             mlLineNumber = lLINE_NUMBER_FIRST
182         End If
183
184         For iLoop = 1 To .CountOfLines
185
186             sMyCodeLine = Trim$(.Lines(iLoop, 1))
187
188             '=================================================================
189             '13-Mar-17 Quick hack to tidy up long spaces before comments
190             sMyCodeLine = Replace$(sMyCodeLine, "    '", "'")        'first pass
191             lLenBefore = Len(sMyCodeLine)
192             sMyCodeLine = Replace$(sMyCodeLine, "  '", "'")
193             lLenAfter = Len(sMyCodeLine)
194             Do While lLenAfter <> lLenBefore
195                 lLenBefore = lLenAfter
196                 sMyCodeLine = Replace$(sMyCodeLine, "  '", "'")
197                 lLenAfter = Len(sMyCodeLine)
198             Loop
199             '=================================================================
200             '=================================================================
201             '07-Apr-17 Quick code to remove pre-existing line numbers
202             Do While Left$(sMyCodeLine, 1) Like "[0-9]"
203                 sMyCodeLine = Trim$(Right$(sMyCodeLine, Len(sMyCodeLine) - 1))
204             Loop
205             '=================================================================
206             bGetsLineNumber = True
207
208             If Len(sMyCodeLine) > 0 Then
209
210                 bIsComment = Left$(sMyCodeLine, 1) = "'"
211
212                 Select Case FirstWord(sMyCodeLine)
                        
                        Case "Option"
213                         bGetsLineNumber = False
214                         bNoIndent = True
215
216                     Case "Declare", "Enum", "Function", "Private", "Public", "Sub", "Type"
217                         bGetsLineNumber = False
218                         bNoIndent = True
219                         bInitialCommentInModule = False
220
221                     Case "If", "IIf"
222                         'For IF lines, default to indent the next line. However check for something after the THEN.
223                         bIndentNextLine = True
224                         'If the next non-space character is NOT "'" (so, it is not a comment) then do not indent the
225                         'next line as it is a one line IF THEN: not the common IF THEN - END IF block. Clear as mud?
226                         If InStr(sMyCodeLine, " Then ") > 0 Then
227                         If Not Replace$(sMyCodeLine, " ", vbNullString) Like "*Then'*" Then bIndentNextLine = False
228                         End If
229                         bInitialCommentInModule = False
230
231                     Case "Do", "For", "With"
232                         bIndentNextLine = True
233                         bInitialCommentInModule = False
234
235                     Case "Select"
236                         bIndentNextLine = True
237                         bInitialCommentInModule = False
238                         bSelectCaseJustStarted = True
239
240                     Case "Case"
241                         bIndentNextLine = True
242                         If bIncase Then bOutdentNow = True
243                         bIncase = True
244
245                     Case "Else", "ElseIf"
246                         bOutdentNow = True
247                         bIndentNextLine = True
248                         bInitialCommentInModule = False
249
250                     Case "End"
251                         If sMyCodeLine Like "End Enum*" Then
252                             bGetsLineNumber = False
253                             bNoIndent = True
254                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
255                         End If
256                         If sMyCodeLine Like "End Function*" Or sMyCodeLine Like "End Sub*" Then
257                             bInProcedure = False
258                             bGetsLineNumber = False
259                             bNoIndent = True
260                             bInitialCommentInModule = True        'to get ready for comments after this sub/function
261                         End If
262                         If sMyCodeLine Like "End If*" Or sMyCodeLine Like "End Select*" Or sMyCodeLine Like "End With*" Then
263                             bOutdentNow = True
264                             bInitialCommentInModule = False
265                         End If
266                         If sMyCodeLine Like "End Select*" Then
267                             bIncase = False
268                         End If
269
270                     Case "Loop", "Next"
271                         bOutdentNow = True
272                         bInitialCommentInModule = False
273
274                     Case Else
275                         If FirstWord(sWholeLine:=sMyCodeLine) Like "*:" Then
276                             bGetsLineNumber = False
277                             bNoIndent = True
278                         End If
279
280                 End Select
281
282             End If
283
284             If bNoIndent Then lHowManyIndents = 0
285             If bOutdentNow Then lHowManyIndents = lHowManyIndents - 1
286             If sMyCodeLine Like "End Select*" Then lHowManyIndents = lHowManyIndents - 1
287             '------------------------------
288             'Last step before new line creation: handle line numbering.
289             If bWantLineNumbers And bInProcedure And bGetsLineNumber Then    ' If want line number at all
290
291                 If bContinuingLine Or (bIsComment And Not bWANT_LINE_NUMBERS_FOR_COMMENTS) Or bSelectCaseCannotHaveLineNumbersBeforeFirstCase Then
292                     'These are special, replace the line number with spaces instead: keeps alignment with other lines.
293                     sNewLine = String(Len(CStr(mlLineNumber)), " ") & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
294                 Else
295                     If bWANT_LINE_NUMBERS_FOR_BLANK_LINES Or Len(sMyCodeLine) > 0 Then  'Want to number blank lines as well as normal lines
296                         mlLineNumber = mlLineNumber + lLINE_NUMBER_INCREMENT
297                         sNewLine = CStr(mlLineNumber) & " " & String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
298                     Else    'don't number blank lines
299                         sNewLine = ""
300                     End If
301                 End If
302
303             Else    'No line numbers
304                 sNewLine = String(lHowManyIndents * lINDENT_STEP, " ") & sMyCodeLine
305             End If
306             .ReplaceLine iLoop, sNewLine
307
308             If sMyCodeLine Like "Private Function *" Or sMyCodeLine Like "Public Function *" _
                    Or sMyCodeLine Like "Function *" Or sMyCodeLine Like "Private Sub *" _
                    Or sMyCodeLine Like "Public Sub *" Or sMyCodeLine Like "Sub *" Then
309                 bInProcedure = True
310                 If Not mbUNIQUE_LINE_NUMBERS Then mlLineNumber = lLINE_NUMBER_FIRST
311             End If
312             '------------------------------
313             If lHowManyIndents = 0 Then lHowManyIndents = 1
314             If bInitialCommentInModule Then lHowManyIndents = 0
315             If bIndentNextLine Then lHowManyIndents = lHowManyIndents + 1
316
317             bContinuingLine = Right$(sMyCodeLine, 1) = "_"
318             bNoIndent = False
319             bIndentNextLine = False
320             bOutdentNow = False
321
322             'At end of code so is after line number handling of "Select Case"
323             If bSelectCaseJustStarted Then
324                 bSelectCaseJustStarted = False 'It is turned off within the same loop as turned on
325                 bSelectCaseCannotHaveLineNumbersBeforeFirstCase = True 'Available for use next time through loop
326             End If
327             If bIncase Then bSelectCaseCannotHaveLineNumbersBeforeFirstCase = False 'Now the first case is reached, turn off
328
329         Next iLoop
330     End With
331
332     Set vbComp = Nothing
333     Set vbProj = Nothing
334
End Sub


Private Function FirstWord(ByRef sWholeLine As String) As String 'NOTE : input is trimmed before calling this function
335
336     Dim ar As Variant
337
338     ar = Split(sWholeLine, " ")
339     FirstWord = ar(LBound(ar))
340     Erase ar
341
End Function
 
Fazza,

Thank you so much for sharing all this code, I really appreciate it.

Cheers,

Mark

sure, mate, cheers
Code:
Option Explicit


Private Sub btnCANCEL_Click()
  gsWbkName = vbNullString
  Unload ufWorkbooks
End Sub


Private Sub btnOK_Click()
  gsWbkName = vbNullString
  On Error Resume Next
  gsWbkName = lbWorkbooks.Value
  Unload ufWorkbooks
End Sub


Private Sub lbWorkbooks_DblClick(ByVal Cancel As MSForms.ReturnBoolean)
  gsWbkName = lbWorkbooks.Value
  Unload ufWorkbooks
End Sub


Private Sub UserForm_Initialize()


  Dim wbkLoop As Excel.Workbook


  For Each wbkLoop In Application.Workbooks
    Select Case wbkLoop.Name
      Case ThisWorkbook.Name, "PERSONAL.XLS", "PERSONAL.XLSB"
      Case Else: ufWorkbooks.lbWorkbooks.AddItem wbkLoop.Name
    End Select
  Next wbkLoop
  Set wbkLoop = Nothing


End Sub
 

Forum statistics

Threads
1,214,920
Messages
6,122,276
Members
449,075
Latest member
staticfluids

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top