Automatically copy formulas and formats when inserting rows.


Posted by Greg on January 31, 2002 5:14 PM

I have a spreadsheet this is used by many different people and I am trying to automate this task so the formulas and formatting continues.

I have conditional formatting and formulas in various cells across all rows. When a person inserts a new row, I want to make sure that the new row has the same formatting and formulas. How can I accomplish this?

Thanks
Greg

Posted by Tom Urtis on January 31, 2002 7:59 PM

One thing you can do is draw a Forms button on the worksheet and attach this macro to it. When someone selects a row or even a single cell, and then clicks that button, a new row would be inserted with formulas and formatting per the row above the selection point. If 3 rows or vertical cells were selected, then 3 new rows would be inserted, as you'd expect. Here's the macro:

Sub InsertRowFormulas()
Application.ScreenUpdating = False
Dim cell As Range
Selection.EntireRow.Insert
For Each cell In Intersect(ActiveSheet.UsedRange, Selection.Offset(-1, 0).EntireRow)
If cell.HasFormula Then
cell.Copy cell.Offset(1, 0)
End If
Next
Application.ScreenUpdating = True
End Sub

One note about the ScreenUpdating lines, if you anticipate only 1 or a few rows at a time to be inserted, then you won't really need the Screen Updating to be turned off. That feature would only make a noticeable difference when a dozen or more rows are inserted, and even then it won't be a big deal. It's your decision as to keeping it in there or not.


HTH

Tom Urtis

Posted by Greg on February 01, 2002 3:51 AM

That worked perfectly. Is it possible to add/edit the macro you have to force it to always insert the row after row 6 ??

Thanks
Greg

: I have a spreadsheet this is used by many different people and I am trying to automate this task so the formulas and formatting continues. : I have conditional formatting and formulas in various cells across all rows. When a person inserts a new row, I want to make sure that the new row has the same formatting and formulas. How can I accomplish this? : Thanks : Greg

Posted by Tom Urtis on February 01, 2002 5:30 AM

Here you go.

Sub InsertRowFormulas()
Application.ScreenUpdating = False
If ActiveCell.Row < 7 Then
MsgBox "Please click OK, then re-select" _
& vbCrLf & "a range starting in at least row 7.", _
16, "Can only insert rows after row 6."
Else
Dim cell As Range
Selection.EntireRow.Insert
For Each cell In Intersect(ActiveSheet.UsedRange, Selection.Offset(-1, 0).EntireRow)
If cell.HasFormula Then
cell.Copy cell.Offset(1, 0)
End If
Next
End If
Application.ScreenUpdating = True
End Sub

Tom Urtis

That worked perfectly. Is it possible to add/edit the macro you have to force it to always insert the row after row 6 ?? : One thing you can do is draw a Forms button on the worksheet and attach this macro to it. When someone selects a row or even a single cell, and then clicks that button, a new row would be inserted with formulas and formatting per the row above the selection point. If 3 rows or vertical cells were selected, then 3 new rows would be inserted, as you'd expect. Here's the macro

Posted by Greg on February 01, 2002 9:05 AM

Perfect - that did the trick. (Plus, you helped me learn a great deal about the power of excel). Thanks for your help.

Greg Here you go. If ActiveCell.Row < 7 Then MsgBox "Please click OK, then re-select" _ & vbCrLf & "a range starting in at least row 7.", _ 16, "Can only insert rows after row 6." Else End Sub Tom Urtis

Posted by Greg on February 01, 2002 10:23 AM

Tom,

Is there a way to disable the right-mouse, menu bar button, and Insert Menu List options for inserting a row? I am trying to idiot-proof this thing as much as possible.

Also, I need to look for a method to disable the box that pops up when you open excel "asking if it is ok to enable macros". I haven't searched for it yet, but thought you may know the answer.

Thanks
Greg Here you go. If ActiveCell.Row < 7 Then MsgBox "Please click OK, then re-select" _ & vbCrLf & "a range starting in at least row 7.", _ 16, "Can only insert rows after row 6." Else End Sub Tom Urtis



Posted by Tom Urtis on February 01, 2002 12:44 PM

Regarding right click:

This will disable it in all sheets. It goes in the workbook module.

Private Sub Workbook_SheetBeforeRightClick(ByVal Sh As Object, ByVal Target As Range, Cancel As Boolean)
Cancel = True
End Sub

Or for just one sheet, not the entire workbook

Private Sub Worksheet_BeforeRightClick
cancel=true
End Sub

OR

Private Sub Worksheet_BeforeRightClick(ByVal Target As Range, Cancel As Boolean)
Cancel = True
End Sub

Regarding enable macros alert, you can only adjust this on your computer, not anyone else's, because it is a computer-level setting. Go to Tools > Macro > Security, Security Level tab, and choose the Low option. Be careful !!! this is nota recommended practice, as it leaves you vulnerable to viruses housed in other imported Excel programs, such as what you might get from an emailed source that you don't know.

Tom Urtis

Tom, Is there a way to disable the right-mouse, menu bar button, and Insert Menu List options for inserting a row? I am trying to idiot-proof this thing as much as possible. Also, I need to look for a method to disable the box that pops up when you open excel "asking if it is ok to enable macros". I haven't searched for it yet, but thought you may know the answer. : Here you go. : Sub InsertRowFormulas() : Application.ScreenUpdating = False : If ActiveCell.Row < 7 Then : MsgBox "Please click OK, then re-select" _ : & vbCrLf & "a range starting in at least row 7.", _ : 16, "Can only insert rows after row 6." : Else : Dim cell As Range : Selection.EntireRow.Insert : For Each cell In Intersect(ActiveSheet.UsedRange, Selection.Offset(-1, 0).EntireRow) : If cell.HasFormula Then : cell.Copy cell.Offset(1, 0) : End If : Next : End If : Application.ScreenUpdating = True : End Sub : Tom Urtis