VBA - USER DEFINED FUNCTIONS

OBJEKTE:   FORMATE


Option Explicit

' Value Variant optional. Falls für Type entweder xlCellTypeConstants oder
' xlCellTypeFormulas angegeben wird, legen Sie mit diesem Argument fest, welche
' Typen von Zellen im Ergebnis mit eingeschlossen werden. Diese Werte können
' addiert werden, wenn mehrere Typen zurückgegeben werden sollen. Standardmäßig
' werden, unabhängig vom Typ, alle Konstanten und Werte ausgewählt. Kann eine
' der folgenden XlSpecialCellsValues-Konstanten sein:
' xlErrors, xlLogical, xlNumbers, xlTextValues,
' xlAllFormatConditions, xlSameFormatConditions

Sub AlleFormelnRotMarkieren()
Selection.SpecialCells(xlFormulas, 1).Select
With Selection.Interior
    .ColorIndex = 3
    .Pattern = xlSolid
    .PatternColorIndex = xlAutomatic
End With
End Sub

Sub AlleKonstatenBlauMarkieren()
Selection.SpecialCells(xlCellTypeConstants, 1).Select
With Selection.Interior
    .ColorIndex = 5
    .Pattern = xlSolid
    .PatternColorIndex = xlAutomatic
End With
End Sub

Sub AlleLeerenZellenGelbMarkieren()
Selection.SpecialCells(xlCellTypeBlanks).Select
With Selection.Interior
    .ColorIndex = 6
    .Pattern = xlSolid
    .PatternColorIndex = xlAutomatic
End With
End Sub

Sub LetzteZelleImBereichGrünMarkieren()
Selection.SpecialCells(xlCellTypeLastCell).Select
With Selection.Interior
    .ColorIndex = 4
    .Pattern = xlSolid
    .PatternColorIndex = xlAutomatic
End With
End Sub

Sub AlleBemerkungenLilaMarkieren()
' Selection.SpecialCells(xlCellTypeNotes).Select
' With Selection.Interior
    ' .ColorIndex = 7
    ' .Pattern = xlSolid
    ' .PatternColorIndex = xlAutomatic
' End With
End Sub

Sub AlleSichtbarenZellenGrauMarkieren()
Selection.SpecialCells(xlCellTypeVisible).Select
With Selection.Interior
    .ColorIndex = 15
    .Pattern = xlSolid
    .PatternColorIndex = xlAutomatic
End With
End Sub

Sub AlleFormatierungenLöschen()
Cells.Select
Selection.ClearFormats
Range("A1").Select
End Sub


Function FarbTyp(Text As String) As Integer
' Farbtypenzuweisung nach Farb-Text
Text = UCase(Text)
Select Case Text
    Case "SCHWARZ"
        FarbTyp = 1
    Case "WEIß"
        FarbTyp = 2
    Case "ROT"
        FarbTyp = 3
    Case "GRÜN"
        FarbTyp = 4
    Case "BLAU"
        FarbTyp = 5
    Case "GELB"
        FarbTyp = 6
    Case "LILA"
        FarbTyp = 7
    Case "HELLBLAU"
        FarbTyp = 8
    Case "ROTBRAUN"
        FarbTyp = 9
    Case "GRÜN"
        FarbTyp = 10
    Case "DUNKELBLAU"
        FarbTyp = 11
    Case "OLIV"
        FarbTyp = 12
    Case "DUNKELLILA"
        FarbTyp = 13
    Case "BLAUGRÜN"
        FarbTyp = 14
    Case "GRAU"
        FarbTyp = 15
    Case "DUNKELGRAU"
        FarbTyp = 16
    Case "GRAU"
        FarbTyp = 17
    Case "DUNKELLILA"
        FarbTyp = 18
End Select
End Function