IE 11

PHP Code:
'   http://www.ozgrid.com/forum/showthread.php?t=198172&page=2&p=763613#post763613
'   
http://www.excelfox.com/forum/f13/bbcode-table-2077/
'   '//Original code is written by Rick Rothstein
    
'//http://www.excelfox.com/forum/f22/get-displayed-cell-color-whether-from-conditional-formatting-or-not-338/
'   
No User FormRun Main Code  Sub BB_Table_Clipboard_PikeFoxAlan()
Option Explicit
' First Declaring Bit of my Code version of the code from Pike, Kris and Rick. http://www.excelfox.com/forum/f17/test-bb-code-2079/#post9642
Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
Declare Function CloseClipboard Lib "User32" () As Long
Declare Function OpenClipboard Lib "User32" (ByVal hwnd As Long) As Long
Declare Function EmptyClipboard Lib "User32" () As Long
Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long
Declare Function SetClipboardData Lib "User32" (ByVal wFormat As Long, ByVal hMem As Long) As Long
Private Const GHND = &H42
Private Const CF_TEXT = 1
Private Const MAXSIZE = 4096
'
'Main Code     http://www.excelfox.com/forum/f17/test-bb-code-2079/#post9643
Sub BB_Table_Clipboard_PikeFoxAlan() '
http://www.excelfox.com/forum/f13/bbcode-table-2077/    http://www.ozgrid.com/forum/showthread.php?t=198172&page=2&p=763613#post763613
     
    
Dim BB_Row As RangeBB_Cells As RangeBB_Range As Range
    Dim BB_Code 
As StringstrFontColour As StringstrBackColour As StringstrAlign As StringstrWidth As String
    
'Const csHEADER_COLOR As String = """#FFFFFF"""
    Const csHEADER_COLOR As String = "black"
    '
Const csHEADER_BACK As String "#888888"
    
Const csHEADER_BACK As String "powderblue"
    
Const csROW_BACK As String "#FFFFFF"
    
Set BB_Range Selection
    BB_Code 
"[color=lightgrey]Using " ExcelVersion "[/color]" vbCrLf 'Give Excel version
    BB_Code = BB_Code & "[size=" & 0 & "][table=" & """" & "class:thin_grid" & """" & "]" & vbNewLine
    '
BB_Code BB_Code "[tr][td][font=Wingdings]v[/font][/td]" vbNewLine
    BB_Code 
BB_Code "[tr=bgcolor:" csHEADER_BACK "][th][COLOR=" csHEADER_COLOR "][sub]Row[/sub]\[sup]Col[/sup][/COLOR][/th]"      ' top left cell
    For Each BB_Cells In BB_Range.Rows(1).Cells '
Column Letters
        strWidth 
Application.WorksheetFunction.RoundUp(BB_Cells.ColumnWidth 7.50)
        
'BB_Code = BB_Code & "[td=" & """" & "bgcolor:#ECF0F0, align:center, width:" & strWidth & """" & "][B]" & Split(BB_Cells.Address, "$")(1) & "[/B][/td]" & vbNewLine
        BB_Code = BB_Code & "[th][CENTER][COLOR=" & csHEADER_COLOR & "]" & ColLtr(BB_Cells.Column) & "[/COLOR][/CENTER][/th]" '
Column Letter Row
    Next BB_Cells
    BB_Code 
BB_Code "[/tr]"
    
For Each BB_Row In BB_Range.Rows 'Row Numbers
        BB_Code = BB_Code & "[tr]"
        '
BB_Code BB_Code "[td=" """" "bgcolor:#ECF0F0, align:center" """" "][B]" BB_Row.Row "[/B][/td]" vbNewLine
        BB_Code 
BB_Code "[td=" """" "bgcolor:" csHEADER_BACK ", align:center" """" "][B]" BB_Row.Row "[/B][/td]" vbNewLine
        
For Each BB_Cells In BB_Row.Cells
            
If BB_Cells.FormatConditions.Count Then
                strFontColour 
objColour(DisplayedColor(BB_CellsFalseFalse))
                
strBackColour objColour(DisplayedColor(BB_CellsTrueFalse))
            Else
                
strFontColour objColour(BB_Cells.Font.Color)
                
strBackColour objColour(BB_Cells.Interior.Color)
            
End If
            
strAlign FontAlignment(BB_Cells)
            
BB_Code BB_Code "[td=" """" "bgcolor:" strBackColour ", align:" strAlign """" "][COLOR=""" strFontColour """]" IIf(BB_Cells.Font.Bold"[B]""") & BB_Cells.Text IIf(BB_Cells.Font.Bold"[/B]""") & "[/COLOR][/td]" vbNewLine
        Next BB_Cells
        BB_Code 
BB_Code "[/tr]" vbNewLine
    Next BB_Row
    BB_Code 
BB_Code "[/table][/size]"
    'End of main table
    BB_Code = BB_Code & "[Table=""width:, class:grid""][tr][td]Sheet: [b]" & BB_Range.Parent.Name & "[/b][/td][/tr][/table]" '
The parent One up the OOP change of the selects range is used to get at the sheet name.
    
ClipBoard_SetData (BB_Code)
    
Set BB_Range Nothing
End Sub
'
'
Some required functions.    http://www.excelfox.com/forum/f17/test-bb-code-2079/#post9644
Private Function objColour(strCell As String) As String
    objColour 
"#" Right(Right("000000" Hex(strCell), 6), 2) & Mid(Right("000000" Hex(strCell), 6), 32) & Left(Right("000000" Hex(strCell), 6), 2)
End Function
 
Private Function 
FontAlignment(ByVal objCell As Object) As String
    With objCell
        Select 
Case .HorizontalAlignment
        
Case xlLeft
            FontAlignment 
"LEFT"
        
Case xlRight
            FontAlignment 
"RIGHT"
        
Case xlCenter
            FontAlignment 
"CENTER"
        
Case Else
            
Select Case VarType(.Value2)
            Case 
8
                FontAlignment 
"LEFT"
            
Case 1011
                FontAlignment 
"CENTER"
            
Case Else
                
FontAlignment "RIGHT"
            
End Select
        End Select
    End With
End 
Function
 
Private Function 
ClipBoard_SetData(MyString As String)
    
Dim hGlobalMemory As LonglpGlobalMemory As Long
    Dim hClipMemory 
As LongAs Long
     
    hGlobalMemory 
GlobalAlloc(GHNDLen(MyString) + 1)
    
lpGlobalMemory GlobalLock(hGlobalMemory)
    
lpGlobalMemory lstrcpy(lpGlobalMemoryMyString)
    If 
GlobalUnlock(hGlobalMemory) <> 0 Then
        MsgBox 
"Could not unlock memory location. Copy aborted."
        
GoTo OutOfHere2
    End 
If
    If 
OpenClipboard(0&) = 0 Then
        MsgBox 
"Could not open the Clipboard. Copy aborted."
        
Exit Function
    
End If
    
EmptyClipboard()
    
hClipMemory SetClipboardData(CF_TEXThGlobalMemory)
OutOfHere2:
    If 
CloseClipboard() = 0 Then
        MsgBox 
"Could not close Clipboard."
    
End If
End Function
 
Private Function 
DisplayedColor(Cell As RangeOptional CellInterior As Boolean True_
    Optional ReturnColorIndex 
As Long True) As Long
     
    Dim X 
As LongTest As BooleanCurrentCell As StringdColor   As Variant
    Dim F   
As StringR  As Range
     
     
'//Original code is written by Rick Rothstein
     '
//http://www.excelfox.com/forum/f22/get-displayed-cell-color-whether-from-conditional-formatting-or-not-338/
     
    
If Cell.Count 1 Then Err.Raise vbObjectError 999, , "Only single cell references allowed for 1st argument."
    
CurrentCell ActiveCell.Address(00)
    For 
1 To Cell.FormatConditions.Count
        With Cell
.FormatConditions(X)
            If .
Type xlCellValue Then
                Select 
Case .Operator
                
Case xlBetween:      Test Cell.Value >= Evaluate(.Formula1) And Cell.Value <= Evaluate(.Formula2)
                Case 
xlNotBetween:   Test Cell.Value <= Evaluate(.Formula1) Or Cell.Value >= Evaluate(.Formula2)
                Case 
xlEqual:        Test Evaluate(.Formula1) = Cell.Value
                
Case xlNotEqual:     Test Evaluate(.Formula1) <> Cell.Value
                
Case xlGreater:      Test Cell.Value Evaluate(.Formula1)
                Case 
xlLess:         Test Cell.Value Evaluate(.Formula1)
                Case 
xlGreaterEqualTest Cell.Value >= Evaluate(.Formula1)
                Case 
xlLessEqual:    Test Cell.Value <= Evaluate(.Formula1)
                
End Select
            
ElseIf .Type xlExpression Then
                Application
.ScreenUpdating False
                 
'Cell.Select
                F = Replace(.Formula1, "$", vbNullString)
                F = Replace(F, CurrentCell, Cell.Address(0, 0))
                 '
Test Evaluate(.Formula1)
                
Test Evaluate(F)
                 
'Range(CurrentCell).Select
                Application.ScreenUpdating = True
            End If
            If Test Then
                If CellInterior Then
                    dColor = IIf(ReturnColorIndex, .Interior.ColorIndex, .Interior.Color)
                    If IsNull(dColor) Then
                        dColor = IIf(ReturnColorIndex, Cell.Interior.ColorIndex, Cell.Interior.Color)
                    End If
                Else
                    dColor = IIf(ReturnColorIndex, .Font.ColorIndex, .Font.Color)
                    If IsNull(dColor) Then
                        dColor = IIf(ReturnColorIndex, Cell.Font.ColorIndex, Cell.Font.Color)
                    End If
                End If
                DisplayedColor = dColor
                Exit Function
            End If
        End With
    Next
    If CellInterior Then
        dColor = IIf(ReturnColorIndex, Cell.Interior.ColorIndex, Cell.Interior.Color)
    Else
        dColor = IIf(ReturnColorIndex, Cell.Font.ColorIndex, Cell.Font.Color)
    End If
    DisplayedColor = dColor
     
End Function
'
Private Function ExcelVersion() As String
    Dim temp                  
As String
    
'On Error Resume Next
#If Mac Then
    Select Case Val(Application.Version)
        Case 11: temp = "Excel 2004"
        Case 12: temp = "Excel 2008" ' 
this should NEVER happen!
        Case 
14temp "Excel 2011"
        
Case 15temp "vNext"
        
Case Else: temp "Unknown"
    
End Select
#Else
    
Select Case Val(Application.Version)
        Case 
9temp "Excel 2000"
        
Case 10temp "Excel 2002"
        
Case 11temp "Excel 2003"
        
Case 12temp "Excel 2007"
        
Case 14temp "Excel 2010"
        
Case 15temp "Excel 2013"
        
Case Else: temp "Unknown"
    
End Select
#End If
    
ExcelVersion temp
End 
Function
'
'
Private Function ColLtr(ByVal iCol As Long) As String
' shg 2012 Alan 2016 http://www.excelforum.com/tips-and-tutorials/1108643-vba-column-letter-from-column-number-explained.html
Good for any positive Long
    
If iCol 0 Then
    ColLtr 
ColLtr((iCol 1) \ 26) & Chr(65 + (iCol 1Mod 26)
    Else
    
End If
End Function