Breaking a reference, keeping the value


Posted by Alex Vincent on October 26, 1999 12:56 AM

OK, this should be fairly easy -- from what I can gather, it's based on simple coding, I just don't know how to do it yet. (I'm familiar with the older members of the BASIC language family, but I've never worked with VBA before last week...)

I have a number of references to outside worksheets, sheets which are contained in other files. I want to break those references without losing the values contained in those files.

I noticed a link to a Microsoft add-in on this site, but I couldn't reach it, so I don't know if it is the solution to my problem.

In any case, I figured out how to do it for one cell:

[H4].Formula=[H4].Value

Now, how do I extend that to a range of cells?

Posted by Ivan Moala on October 26, 1999 3:03 AM

Hi Alex,
Try the following macro which will search for all
formulas with links to other workbooks and replace
them with a the cell value.

Sub ResetLinks()
Dim Fml
Dim cell
Dim WS_LinkName
Dim i As Integer

'***************************************
'* Find links and replace with values *
'* created 26/10/99 IF Moala *
'***************************************

WS_LinkName = ActiveWorkbook.LinkSources(xlExcelLinks)
If Not IsEmpty(WS_LinkName) Then
ReDim ws(UBound(WS_LinkName))
For i = 1 To UBound(WS_LinkName)
ws(i) = WS_LinkName(i)
Next i
Else
MsgBox "No Links found!": End
End If

On Error Resume Next
Set Fml = Selection.SpecialCells(xlCellTypeFormulas, 23)
On Error GoTo 0
If IsEmpty(Fml) Then MsgBox "No formulas!": End

For Each cell In Fml.Cells
For i = 1 To UBound(WS_LinkName)
If Left(cell.Formula, 6) = "='" & Left(ws(i), 4) Then
cell.Value = cell.Value
End If
Next
Next
End Sub


Ivan


Posted by Ivan Moala on October 26, 1999 3:24 AM

I forgot to add that the workbook your formulas
are linked to MUST be closed for this to work!!

Ivan

Posted by Jamie on October 26, 1999 8:53 AM

This maybe too simple but, what about copy the cell and then paste special just values?
You can use it on one cell, a range or a whole page. Macroing this is a proverbial piece of!


Posted by Ivan Moala on October 26, 1999 7:13 PM

Except when you have a number of refereces throughout
your work book that you may have forgotten about
or for which doing it manually (due to number and location) becomes too tedious, other wise I agree.

Ivan

Posted by Alex Vincent on October 26, 1999 10:27 PM

Forgive me for being amused, but this above line appears somewhat useless...

Did you mean:

cell.Formula = cell.Value

?



Posted by Ivan Moala on October 27, 1999 12:25 AM

Alex, No It won't work with this line in.
Removing the lies and replacing it with the above will
not give you the right answer.
What the line is doing is trying to differentiate
between a LINKED formula and a normal formula
ie. a linked formulas first few characters will start with the ='D\ (the drive letter).


Ivan