VBA - USER DEFINED FUNCTIONS

OBJEKTE:   ZELLEN


'Elegantere Lösung durch die MIT-Konstruktion
Sub Test5()
With ActiveSheet.Cells(1, 1)
    .Formula = "=Sin(180)"
    .Font.Name = "Arial"
    .Font.Bold = True
    .Font.Size = 8
End With
End Sub

Sub Test6()
With ActiveSheet.Cells(1, 1)
    .Formula = "=Sin(180)"
    With .Font
        .Name = "Arial"
        .Bold = True
        .Size = 8
    End With
End With
End Sub

'Objekt.Eigenschaft = Ausdruck
Sub Test1()
ActiveCell.RowHeight = 14
ActiveCell.Value = "Jahresumsatz"
ActiveCell.Locked = True
End Sub

'Variable = Objekt.Eigenschaft
Sub Test2()
Sheets("Tabelle1").Select 'Wählt Blatt Tabelle1 aus
'Weist der Zelle A10 den Wert der Zelle A9 zu
ActiveSheet.Cells(10, 1).Formula = ActiveSheet.Cells(9, 1).Formula
End Sub

'Objekt.Methode Argumente
Sub Test3()
DiesesWort = ActiveSheet.CheckSpelling(IgnoreUppercase:=True)
MsgBox DiesesWort
If DiesesWort = True Then
    MsgBox "Alles OK!"
Else
    MsgBox "Achtung: Fehler!"
End If
End Sub

'Anwenden von Aktionen auf ein Objekt
Sub Test4()
ActiveSheet.Cells(1, 1).Formula = "=Sin(180)"
ActiveSheet.Cells(1, 1).Font.Name = "Arial"
ActiveSheet.Cells(1, 1).Font.Bold = True
ActiveSheet.Cells(1, 1).Font.Size = 8
End Sub

' Übungen zur Schreibweise für Eigenschaften von Objekten
' Objekt.Eigenschaft = Ausdruck
Sub Aktive_Zelle_Aendern()
ActiveCell.RowHeight = 24
ActiveCell.Value = "Jahresumsatz"
ActiveCell.Locked = True
ActiveCell.ColumnWidth = 50
ActiveCell.EntireColumn.AutoFit
End Sub

' Variable = Objekt.Eigenschaft
' Weist der Zelle A10 den Wert der Zelle A9 zu
' Objekt.Methode Argumente

Sub Rechtschreib_Kontrolle()
DiesesWort = ActiveSheet.CheckSpelling _
(CustomDictionary:="BENUTZER.DIC", IgnoreUppercase:=True)
MsgBox DiesesWort
If DiesesWort = True Then
    MsgBox "Alles OK!"
Else
    MsgBox "Sorry! Etwas war nicht richtig."
End If
End Sub

' Anwenden der With-Klausel auf ein Objekt
Sub With_Einfach()
Range("A1").Select
With Selection
    .Formula = "=5*(3+7)"
    .Font.Name = "Arial"
    .Font.Bold = True
    .Font.Italic = True
    .Font.Size = 8
End With
End Sub

' Anwenden von mehreren With-Klauseln auf ein Objekte
Sub With_Geschachtelt()
Range("A1").Select
With Selection
    .Formula = "=5*(3+7)"
    With .Font
        .Name = "Arial"
        .Bold = True
        .Size = 8
    End With
End With
End Sub

' Variablenaustausch innerhalb zweier Zellen
Sub Zeltausch()
Dim Temp As Variant
Temp = Range("A1").Value
Range("A1").Value = Range("B1").Value
Range("B1").Value = Temp
End Sub

'Variableninhalte übergeben; Variablen Zellbez1; Zellbez2
'vorher über andere Sub-Routine definieren
Sub TauscheZellen(Zellbez1, Zellbez2)
Temp = Zellbez1.Value
Zellbez1.Value = Zellbez2.Value
Zellbez2.Value = Temp
End Sub

'Zelle markieren und mit Wert füllen
Sub Variable_Abfragen()
Range("A5").Select
ActiveCell.FormulaR1C1 = "Umsätze West"
End Sub