Marco to copy and paste special value
Posted by Pat on January 16, 2002 10:34 AM
I need a Marco that will look at A:2:A2500 and if it has a number in it go to G2:G2500, and copy the cells and paste special value. If there is not a number in column A it should not copy and paste. This will be used in excel 97. Thank for taking the time to help.
Posted by Damon Ostrander on January 16, 2002 10:49 AM
Hi Pat,
Here's a macro that will do this.
Sub CopyAtoG()
Dim x As Variant
x = [A2:A2500]
[G2:G2500]= x
End Sub
Happy computing.
Damon
Posted by Pat on January 16, 2002 11:14 AM
maybe I did not explain it right, I have formulas in column G, I want it to copy column G and paste special values back in to column G, keeping the info but doing away with the formulas for the cells in column A that have a number
Posted by Damon Ostrander on January 16, 2002 12:45 PM
Okay, then this...
Hi again Pat,
Sorry I misinterpreted your problem. This could have been done just as easily with a copy/pastespecial, but this method is way more cool.
Sub CopyValuesOnly()
Dim x As Variant
Dim r As Range
Set r = [G2:G500]
x = r: r.Clear: r = x
End Sub
Here it is using the copy/pastespecial. This has the advantage (or disadvantage, depending on what you want) of preserving the cell formats.
Sub PasteValuesOnly()
Dim r As Range
Set r = [G2:G500]
r.Copy
r.PasteSpecial xlPasteValues
Application.CutCopyMode = False
End Sub
Damon
Posted by Pat on January 16, 2002 1:03 PM
but I only want to copy and paste if there is a number in the same row in column A
Posted by Damon Ostrander on January 16, 2002 3:40 PM
Yet another try (going for the record).
Hi Pat,
Did I interpret it right this time?
Sub ValueIfNumeric()
Dim c As Range 'cell in column A
Dim r As Range 'cell in column G
Dim t As Variant 'temporary storage value
For Each c In [A2:A500]
If IsNumeric(c.Value) Then
Set r = c.Offset(0, 6) 'offset to column G
t = r: r.ClearContents: r = t
End If
Next c
End Sub
Damon
Posted by Pat on January 16, 2002 4:37 PM
Damon, PLEASE take another look at the example
I will try to explain better I only want to copy and paste special value, in G2:G2500 if there is a number in A2:A2500. Example A2 is15, A3 is Blank, G2 is =H1, valve in H1 is test, G3 is = H3, valve in H3 is this, when the Marco is run it should copy G2 and paste special value back in G2, taking the formula out, G3 should keep the formula =H3 because there is not a number in A3. Hope I made it clearer this time. Thanks for taking the time to help and for having so much patience.
A G H
2 15 =H1 TEST
3 =H3 THIS
after Marco is run I need this
A G H
2 15 TEST TEST
3 =H3 THIS
Posted by Tom Urtis on January 16, 2002 11:44 PM
A cure for late night boredom
Pat,
I'm sure Damon would've done this first thing tomorrow morning but I got bored tonite so here's my stab at it. It's a loop but only takes about 2 seconds. I hope I guessed right on what you need.
Sub CPSV_Number()
Application.ScreenUpdating = False
Range("A2").Activate
Do While ActiveCell.Row < 2501
If Not IsNumeric(ActiveCell) Or ActiveCell.Value = "" Then
ActiveCell.Offset(1, 0).Select
Else
ActiveCell.Offset(0, 6).Value = ActiveCell.Offset(0, 6).Value
ActiveCell.Offset(1, 0).Activate
End If
Loop
Range("A1").Select
Application.ScreenUpdating = True
End Sub
Any help?
Tom Urtis
Posted by Pat on January 17, 2002 3:46 AM
THATS IT, thanks Tom & Damon
I'm sure Damon would've done this first thing tomorrow morning but I got bored tonite so here's my stab at it. It's a loop but only takes about 2 seconds. I hope I guessed right on what you need. Sub CPSV_Number()
: I will try to explain better I only want to copy and paste special value, in G2:G2500 if there is a number in A2:A2500. Example A2 is15, A3 is Blank, G2 is =H1, valve in H1 is test, G3 is = H3, valve in H3 is this, when the Marco is run it should copy G2 and paste special value back in G2, taking the formula out, G3 should keep the formula =H3 because there is not a number in A3. Hope I made it clearer this time. Thanks for taking the time to help and for having so much patience. : A G H : 2 15 =H1 TEST : 3 =H3 THIS : after Marco is run I need this : A G H : 2 15 TEST TEST : 3 =H3 THIS :
Posted by Damon Ostrander on January 17, 2002 9:00 AM
Re: THATS IT, thanks Tom & Damon
Hi again Pat and Tom,
Just for the record, this is what my solution would have been. I had failed to take into account, as Tom did, that the IsNumeric interprets an empty cell as zero, a numeric value. I thought you might like to see this solution because it does not use a copy and paste at all, and therefore does not require turning screen updating off in order to run fast.
Sub ValueIfNumeric()
Dim c As Range
Dim r As Range
Dim t As Variant
For Each c In [A2:A30]
If IsNumeric(c.Value) And Not c.Value = "" Then
Set r = c.Offset(0, 6) 'offset to column G
t = r: r.ClearContents: r = t
End If
Next c
End Sub
Thanks, Tom!
Damon : Pat, : I'm sure Damon would've done this first thing tomorrow morning but I got bored tonite so here's my stab at it. It's a loop but only takes about 2 seconds. I hope I guessed right on what you need. : Sub CPSV_Number() : Application.ScreenUpdating = False : Range("A2").Activate : Do While ActiveCell.Row < 2501 : If Not IsNumeric(ActiveCell) Or ActiveCell.Value = "" Then : ActiveCell.Offset(1, 0).Select : Else : ActiveCell.Offset(0, 6).Value = ActiveCell.Offset(0, 6).Value : ActiveCell.Offset(1, 0).Activate : End If : Loop : Range("A1").Select : Application.ScreenUpdating = True : End Sub : : Any help? : Tom Urtis :
Posted by Pat on January 17, 2002 10:14 AM
Thanks to both of you again, Damon your is a little faster (nt)
Just for the record, this is what my solution would have been. I had failed to take into account, as Tom did, that the IsNumeric interprets an empty cell as zero, a numeric value. I thought you might like to see this solution because it does not use a copy and paste at all, and therefore does not require turning screen updating off in order to run fast. Dim c As Range Dim r As Range Dim t As Variant For Each c In [A2:A30] If IsNumeric(c.Value) And Not c.Value = "" Then Next c Thanks, Tom!