Die Community zu .NET und Classic VB.
Menü

VB 5/6-Tipp 0630: Grafik in Grautönen zeichnen per ASM

 von 

Beschreibung 

Dieser Tipp stammt aus eine Reihe von Tipps rund um das Thema Grafikmanipulation mit ASM. Das Modul "asm_001ROU.bas" ist daher in allen Tipps das Gleiche. In diesem Tipp wird gezeigt, wie man eine Grafik in Grautönen zeichnet. Dabei wird sowohl eine Lösung mit VB, wie auch eine Lösung in ASM (der Code liegt bei) angeboten.

Schwierigkeitsgrad:

Schwierigkeitsgrad 3

Verwendete API-Aufrufe:

CLSIDFromString, CallWindowProcA (CallWindowProc), RtlMoveMemory (CopyMemory), CreateDIBSection, OleCreatePictureIndirect (CreatePic), DeleteObject, GetDC, GetDIBits, GetObjectA (GetObject), ReleaseDC

Download:

Download des Beispielprojektes [10,03 KB]

'Dieser Quellcode stammt von http://www.activevb.de
'und kann frei verwendet werden. Für eventuelle Schäden
'wird nicht gehaftet.

'Um Fehler oder Fragen zu klären, nutzen Sie bitte unser Forum.
'Ansonsten viel Spaß und Erfolg mit diesem Source!

'----------- Anfang Projektdatei prjGrayStyle.vbp -----------
' Die Komponente 'Microsoft Common Dialog Control 6.0 (SP3) (comdlg32.ocx)' wird benötigt.

'--- Anfang Formular "frm_GrayScale" alias frm_GrayScale.frm  ---
' Steuerelement: Schaltfläche "Command4"
' Steuerelement: Schaltfläche "Command3"
' Steuerelement: Schaltfläche "Command2"
' Steuerelement: Schaltfläche "Command1"
' Steuerelement: Bildfeld-Steuerelement "Picture1"
' Steuerelement: Standarddialog-Steuerelement "CommonDialog1"



'----------------------------------------------------------------------
' (softKUS) - VIII/2003
'----------------------------------------------------------------------
' Die Funktion "(Gray)Scale" wandelt alle Farben in Grautöne um.
'
' Für die Umsetzung wird eine Assembler-(Maschinensprache)-Routine
' benutzt, deren Funktionsweise nicht ohne weiteres ersichtlich ist.
' Deshalb ist eine Basic-Funktion, basScale, angefügt. Per Mausklick
' auf Command3 kann zwischen Basic- und Assemblerbenutzung
' hin- und hergeschaltet werden.
'
' Das Beispiel besteht aus drei Modulen:
' 1. Form1    - Dient bloß zur Demonstration
' 2. Module1  - Enthält grundlegendes zum Lesen/Schreiben der Bilder
' 3. Module2  - Enthält die eigentliche Bildbearbeitung
'               (asmScale/basScale)
'
' Die ASM-Routine, asmScale, kann auch völlig losgelöst vom hiesigen
' Rahmen benutzt werden. Es muß lediglich gewährleistet sein, daß der
' erste Parameter (lpAsmBmpPara) auf eine genau nach unten
' beschriebenem Muster erstellte und mit gültigen Werten
' initialisierte Struktur verweist - andernfalls kommt es
' garantiert zum PC-Absturz.
'
'----------------------------------------------------------------------
'
' Ein Formular mit:
' Picture1, Command1 bis Command4, CommonDialog1
'
'----------------------------------------------------------------------

Option Explicit
Option Base 0


' *
' **
' *** Konstanten
' **
' *

' größerer Wert => größere Form
Private Const XYcm      As Long = 567
Private Const Ftxt      As String = "asm-Beispiel Scale"


' *
' **
' *** Variablen
' **
' *

' udt: Datenstruktur für ASM-Routine
Dim abp                 As asmBmpPara

' bin: Bilddaten
Dim src()               As Byte

' bin: Puffer für die Bildbearbeitung
Dim tgt()               As Byte

' log: .T.=Assember, .F.=Basic
Dim pmd                 As Boolean

Private Sub Form_Load()
    
    ' Initialisieren der Byte-Arrays
    ReDim src(1, 1)
    
    ' (vermeidet Zugriffsfehler)
    ReDim tgt(1, 1)
    
    With Me
        .ScaleMode = vbTwips
        .Width = (Me.Controls.Count * 2 - 2) * XYcm
        .Height = (Me.Controls.Count * 2 - 2) * XYcm
        .Caption = Ftxt
    End With
    
    Command1.Caption = "Bild laden"
    Command2.Caption = "Undo"
    Command3.Caption = "Basic"
    Command4.Caption = "Scale"
    Picture1.ScaleMode = vbTwips
    
    pmd = True
End Sub

' dummy Bild erzeugen
Private Sub Form_Initialize()
    Dim X1 As Long
    
    Randomize Timer
    Picture1.AutoRedraw = True
    
    For X1 = 1 To 400
        Picture1.DrawWidth = 1 + Rnd() * 30
        Picture1.Line (Rnd * Picture1.Width, _
        Rnd * Picture1.Height)-(Rnd * Picture1.Width, _
        Rnd * Picture1.Height), RGB(Rnd * 255, Rnd * 255, Rnd * 255)
    Next X1
    
    Picture1.AutoRedraw = False
    
    If ReadData(Picture1.Image, abp, src, tgt, pmd, False) Then _
        WriteData Picture1, abp.src, True
    
End Sub

Private Sub Form_Resize()
    Dim dfw As Long
    Dim dfh As Long
    Dim tmp As Long
    
    dfw = Me.Width - Me.ScaleWidth
    dfh = Me.Height - Me.ScaleHeight
    tmp = ((Me.Controls.Count - 3) * 2.25 + 0.25) * XYcm + dfw
    
    If Me.Width < tmp Then Me.Width = tmp
    If Me.Height < 5 * XYcm Then Me.Height = 5 * XYcm
    
    With Command1
        
        ' Bild laden
        .Top = 0.25 * XYcm
        .Left = 0.25 * XYcm
        .Width = 2 * XYcm
        .Height = 0.5 * XYcm
    End With
    
    With Command4
        
        ' Scale
        .Top = 0.25 * XYcm
        .Left = 2.5 * XYcm
        .Width = 2 * XYcm
        .Height = 0.5 * XYcm
    End With
    
    With Command2
        
        ' Undo
        .Top = 0.25 * XYcm
        .Left = Me.Width - 4.5 * XYcm - dfw
        .Width = 2 * XYcm
        .Height = 0.5 * XYcm
    End With
    
    With Command3
        
        ' bas/asm
        .Top = 0.25 * XYcm
        .Left = Me.Width - 2.25 * XYcm - dfw
        .Width = 2 * XYcm
        .Height = 0.5 * XYcm
    End With
    
    With Picture1
        .Top = 1 * XYcm
        .Left = 0.25 * XYcm
        .Width = Me.Width - 0.5 * XYcm - dfw
        .Height = Me.Height - 1.25 * XYcm - dfh
    End With
End Sub

Private Sub Picture1_DblClick()
    Form_Initialize
End Sub

' Bild laden
Private Sub Command1_Click()
    
    ' obj: enthält das zu ladende Bild
    Dim pic As IPicture
    
    On Error Resume Next
    
    With CommonDialog1
        .CancelError = True
        .Flags = &H281800
        .Filter = "Bilder |*.bmp;*.jpg||"
        .ShowOpen
        
        If Err = 0 Then
            Set pic = LoadPicture(.FileName)
            
            If pic Is Nothing Then
                MsgBox "Bild konnte nicht geladen werden"
                
            ElseIf ReadData(pic, abp, src, tgt, pmd) Then
                
                ' alles okay => setze pic auf die PictureBox
                Set Picture1.Picture = pic
            End If
        End If
    End With
    
    Picture1.SetFocus
End Sub

' Undo
Private Sub Command2_Click()
    
    ' Änderung am Bild zurücknehmen
    WriteData Picture1, abp.src
    Picture1.SetFocus
End Sub

' Umschalten zw. bas und asm
Private Sub Command3_Click()
    pmd = Not pmd
    Command3.Caption = Choose(pmd + 2, "Basic", "Assembler")
    
    If pmd = False And Picture1.Picture.Handle <> 0 _
        And VarPtr(tgt(1, 1)) <> abp.tgt.bmBits Then
        
        ' Wenn abp.tgt direkt auf den Speicher der Bitmap
        ' weist, muss für die Basic-Routine auf ein ByteArray
        ' umgelenkt werden. Dazu kann auch mit einer SAVEARRAY-
        ' Struktur gearbeitet werden - das führte hier aber zu weit.
        
        ReDim tgt(1 To UBound(src, 1), 1 To UBound(src, 2))
        abp.tgt.bmBits = VarPtr(tgt(1, 1))
    End If
    
    Picture1.SetFocus
End Sub

Private Sub Command4_Click()
    Dim B1 As Boolean
    
    If Picture1.Picture.Handle = 0 Then
        
        ' deaktiviert/kein Bild geladen => ignorieren
        
    ElseIf pmd Then
        B1 = asmScale(VarPtr(abp))
    Else
        B1 = basScale(src, tgt)
    End If
    
    ' geändertes Bild ausgeben
    If B1 Then WriteData Picture1, abp.tgt
    Picture1.SetFocus
End Sub

'--- Ende Formular "frm_GrayScale" alias frm_GrayScale.frm  ---
'------ Anfang Modul "asm_001ROU" alias asm_001ROU.bas ------

Option Explicit
Option Base 0

' *
' **
' *** Konstanten
' **
' *

' gdi/ole
Private Const S_OK              As Long = 0
Private Const BI_RGB            As Long = 0
Private Const DIB_RGB_COLORS    As Long = 0

Private Const IID_IPicture      As String = _
    "{7BF80980-BF32-101A-8BBB-00AA00300CAB}"



' *
' **
' *** Strukturen
' **
' *

' Windows-Standard
' udt: Windows-Bitmap-Struktur
Public Type BITMAP
    
    ' -> Einlesen der Bildinformationen
    ' mit GDI_GetObject()
    bmType                      As Long
    bmWidth                     As Long
    bmHeight                    As Long
    bmWidthBytes                As Long
    bmPlanes                    As Integer
    bmBitsPixel                 As Integer
    bmBits                      As Long
End Type

' udt: Windows-Bitmap-Struktur
Public Type BITMAPINFOHEADER
    
    ' -> Erstellen von Bildern im Speicher,
    ' mit GDI_CreateDibSection
    biSize                      As Long
    biWidth                     As Long
    biHeight                    As Long
    
    ' -> Einlesen von Bilddaten (binär)
    ' mit GDI_GetDiBits
    biPlanes                    As Integer
    biBitCount                  As Integer      '
    
    ' wird nur als Unterstruktur von
    ' BITMAPINFO benötigt (s.u.)
    biCompression               As Long
    biSizeImage                 As Long
    biXPelsPerMeter             As Long
    biYPelsPerMeter             As Long
    biClrUsed                   As Long
    biClrImportant              As Long
End Type

' udt: Windows-Bitmap-Struktur
Public Type BITMAPINFO
    bmiHeader                   As BITMAPINFOHEADER
    bmiColors                   As Long
End Type

' udt: PictureDescription
Private Type PictDesc
    
    ' -> Erstellen eines IPicture-Objektes
    ' mit OleCreatePictureIndirect
    cbSizeofStruct              As Long
    picType                     As Long
    hImage                      As Long
    xExt                        As Long
    yExt                        As Long
End Type


' von asm-Routinen genutzte Struktur
' udt: AsmStruktur
Public Type asmBmpPara
    
    ' -> fasst Infos über Herkunftsdaten
    ' und Zieldaten zusammen
    ' dient vor allem dazu, die Anzahl
    ' der Funktionsparamter zu begrenzen
    src                         As BITMAP
    tgt                         As BITMAP
    srcExpansion                As Long
End Type


' *
' **
' *** Externe Funktionen
' **
' *

' div

' hiermit werden Daten recht schnell kopiert
Public Declare Sub CopyMemory Lib "kernel32" Alias _
    "RtlMoveMemory" (ByRef hpvDest As Any, _
    ByRef hpvSource As Any, ByVal cbCopy As Long)


' hiermit wird die asm-Routine aufgerufen
Public Declare Function CallWindowProc Lib "user32" Alias _
    "CallWindowProcA" (ByRef lpPrevWndFunc As Long, _
    ByVal hWnd As Long, ByVal msg As Long, ByVal _
    wParam As Long, ByVal lParam As Long) As Long



' GDI (graphical device interface)

' Erstellen eines Gerätekontextes
Private Declare Function GetDC Lib "user32" _
    (ByVal hWnd As Long) As Long


' Freigeben eines Gerätekontextes
Private Declare Function ReleaseDC Lib "user32" _
    (ByVal hWnd As Long, ByVal hDC As Long) As Long


' Einlesen von Informationen über GDI-Objekte (z.B. Bilder)
Private Declare Function GetObject Lib "gdi32" Alias _
    "GetObjectA" (ByVal hObject As Long, _
    ByVal nCount As Long, ByRef lpObject As Any) As Long


' Löschen eines GDI-Objektes
Private Declare Function DeleteObject Lib "gdi32" _
    (ByVal hObject As Long) As Long


' Erstellen eines geräte-unabhängigen Bildes
' (Device Independent Bitmap, DIB)
Private Declare Function CreateDIBSection Lib "gdi32" _
    (ByVal hDC As Long, ByRef pbmi As BITMAPINFO, _
    ByVal iUsage As Long, ByRef ppvBits As Long, _
    ByVal hSection As Long, ByVal dwOffset As Long) As Long


' Einlesen binärer Bilddaten
Private Declare Function GetDIBits Lib "gdi32" _
    (ByVal hDC As Long, ByVal hBM As Long, _
    ByVal uStartScan As Long, ByVal cScanLines As Long, _
    ByRef lpvBits As Any, ByRef lpBmi As BITMAPINFO, _
    ByVal uUsage As Long) As Long


' OLE (Object Linked Embedding, heute: COM oder ActiveX genannt)

' Umwandeln eines CLSID-Strings in Binärcode
Private Declare Function CLSIDFromString Lib "ole32" _
    (ByVal lpszProgID As Long, ByVal pCLSID As Long) As Long


' Erstellen eines IPicture-Objektes aus einem GDI-Bitmap-Handle
Private Declare Function CreatePic Lib "olepro32" Alias _
    "OleCreatePictureIndirect" (ByRef lpPictDesc As PictDesc, _
    ByVal riid As Long, ByVal fPictureOwnsHandle As Long, _
    ByRef ipic As IPicture) As Long


Function ReadData(pic As IPicture, abp As asmBmpPara, _
    src() As Byte, tgt() As Byte, _
    Optional pmd As Boolean = True, _
    Optional eMD As Boolean = True) As Boolean
    
    
    ' infos über das einzulesende Bild
    Dim bmp   As BITMAP
    
    ' erweiterte infos über das einzulesende Bild
    Dim bmi   As BITMAPINFO
    
    ' Gerätekontext-Handle
    Dim hDC   As Long
    
    ' Zeiger auf die binären Bilddaten
    Dim ptr   As Long
    Dim tmp   As Long
    
    ' Einlesen der Bitmapinfos
    If GetObject(pic.Handle, Len(bmp), bmp) = 0 Then
        
        If eMD Then _
            MsgBox "Bildinformationen konnten nicht gelesen werden"
        
    ElseIf pmd = True And bmp.bmBits <> 0 _
        And bmp.bmBitsPixel = 32 Then
        
        ' wenn die Daten im richtigen Format vorliegen,
        ' diesen Pointer nehmen
        ptr = bmp.bmBits
        
    Else
        
        ' sonst per GDI-Funktion konvertieren lassen und
        ' im tgt-bArray() speichern
        With bmi.bmiHeader
            .biSize = Len(bmi.bmiHeader)
            .biCompression = BI_RGB
            .biHeight = bmp.bmHeight
            .biWidth = bmp.bmWidth
            .biPlanes = 1
            .biBitCount = 32
            .biSizeImage = .biWidth * 4 * .biHeight
            
            ReDim tgt(1 To .biWidth * 4, 1 To .biHeight)
            hDC = GetDC(0)
            
            If hDC = 0 Then
                
                If eMD Then _
                    MsgBox "Gerätekontext konnte nicht erzeugt werden"
                
            ElseIf GetDIBits(hDC, pic.Handle, 0, .biHeight, _
                tgt(1, 1), bmi, DIB_RGB_COLORS) Then
                
                ptr = VarPtr(tgt(1, 1))
                
            Else
                
                ' bei Fehler: tgt-bArray wieder auf usrprüngliche
                ' Dimension setzen
                ReDim tgt(1 To UBound(src, 1), 1 To UBound(src, 2))
                
                If eMD Then _
                    MsgBox "Bilddaten konnten nicht gelesen werden"
            End If
            
            If hDC Then ReleaseDC 0, hDC
        End With
    End If
    
    If ptr Then
        bmp.bmBitsPixel = 32
        bmp.bmWidthBytes = bmp.bmWidth * 4
        tmp = bmp.bmWidthBytes * bmp.bmHeight
        
        ' src-bArray dimensionieren und mit Bilddaten füllen
        ReDim src(1 To bmp.bmWidthBytes, 1 To bmp.bmHeight)
        CopyMemory src(1, 1), ByVal ptr, tmp
        
        ' asmBmpPara-Struktur setzen
        abp.src = bmp
        abp.src.bmBits = VarPtr(src(1, 1))
        
        abp.tgt = bmp
        abp.tgt.bmBits = ptr
        
        ReadData = True
    End If
End Function

Function WriteData(pbx As PictureBox, bmp As BITMAP, _
    Optional force As Boolean = False) As Boolean
    
    
    ' Neues Picture-Objekt
    Dim pic         As IPicture
    
    ' infos über das zu überschreibende Bild
    Dim tmp         As BITMAP
    
    ' erw. infos über das Bild
    Dim bmi         As BITMAPINFO
    
    ' info zum Erstellen eines neuen Pictures
    Dim dsc         As PictDesc
    
    ' temporär benutzter Gerätekontext
    Dim hDC         As Long
    
    ' Zeiger auf die binären Bilddaten
    Dim ptr         As Long
    Dim flg         As Long
    
    ' clsid des IPicture-Objektes
    Dim iid(15)     As Byte
    
    flg = pbx.Picture.Handle And (force = False)
    If flg Then flg = GetObject(flg, Len(tmp), tmp)
    
    If bmp.bmBits = tmp.bmBits Then
        
        ' tgt weist direkt auf den
        ' Bildobjekt-Speicher => nothing to do
        pbx.Refresh
        WriteData = True
        
    ElseIf flg > 0 And tmp.bmBits <> 0 _
        And bmp.bmWidth = tmp.bmWidth And _
        bmp.bmHeight = tmp.bmHeight And _
        bmp.bmBitsPixel = tmp.bmBitsPixel Then
        
        
        ' wenn das Ziel dasselbe Datenformat aufweist,
        ' einfach kopieren
        CopyMemory ByVal tmp.bmBits, ByVal bmp.bmBits, _
            bmp.bmWidthBytes * bmp.bmHeight
        
        pbx.Refresh
        WriteData = True
        
    Else
        
        ' sonst per OLE-Funktion ein neues
        ' IPicture-Objekt erstellen
        dsc.cbSizeofStruct = Len(dsc)
        dsc.picType = vbPicTypeBitmap
        
        With bmi.bmiHeader
            .biSize = Len(bmi.bmiHeader)
            .biCompression = BI_RGB
            .biBitCount = 32
            .biHeight = bmp.bmHeight
            .biWidth = bmp.bmWidth
            .biPlanes = 1
            .biSizeImage = bmp.bmWidthBytes * bmp.bmHeight
        End With
        
        ' 1. Gerätekontext
        hDC = GetDC(0)
        
        ' 2. DIB-Section
        If hDC Then dsc.hImage = _
            CreateDIBSection(hDC, bmi, DIB_RGB_COLORS, ptr, 0, 0)
        
        If hDC = 0 Then
            MsgBox "Gerätekontext konnte nicht erzeugt werden"
            
        ElseIf dsc.hImage = 0 Or ptr = 0 Then
            MsgBox "Bildkopie konnte nicht erstellt werden"
            
        Else
            CopyMemory ByVal ptr, ByVal bmp.bmBits, _
                bmp.bmWidthBytes * bmp.bmHeight
            
            If CLSIDFromString(StrPtr(IID_IPicture), _
                VarPtr(iid(0))) <> S_OK Then
                
                MsgBox "OLE Fehler"
                
            ' 3. IPicture-Objekt
            ElseIf CreatePic(dsc, VarPtr(iid(0)), _
                    True, pic) <> S_OK Then
                
                MsgBox "OLE picture creation error"
                
            Else
                
                ' ... und das Ergebnis auf die PictureBox setzen
                Set pbx.Picture = Nothing
                Set pbx.Picture = pic
                dsc.hImage = 0
                WriteData = True
            End If
        End If
        
        If hDC Then ReleaseDC 0, hDC
        If dsc.hImage Then DeleteObject dsc.hImage
    End If
End Function
'------- Ende Modul "asm_001ROU" alias asm_001ROU.bas -------
'--- Anfang Modul "asm_GrayScale" alias asm_GrayScale.bas ---

Option Explicit

' asmScale
'
' CALL asmScale(ptr:lpAsmBmpPara, [rf:redfct], _
'              [gf:greenfct], [bf:bluefct])
'
' IN:   lng:ptr Points to asmBmpPara-structure
'       lng:rf  red   factor     (default = 71)
'       lng:gf  green factor     (default = 707)
'       bol:bf  blue  factor     (default = 222)
'
' OUT:  bol     success
'

Function asmScale(lpAsmBmpPara As Long, _
    Optional rf As Long = 71, _
    Optional gf As Long = 707, _
    Optional BF As Long = 222) As Boolean
    
    Static asm(19) As Long
    
    If asm(0) = 0 Then
        asm(0) = &HEC8B5590
        asm(1) = &H68575653
        asm(2) = &H3E8
        asm(3) = &H8B085D8B
        asm(4) = &H7B8B1473
        asm(5) = &H1C4B8B2C
        asm(6) = &H204BAF0F
        asm(7) = &H8BDB33AD
        asm(8) = &H8AD48AD3
        asm(9) = &H55AF0FD8
        asm(10) = &H5DAF0F10
        asm(11) = &HC1DA030C
        asm(12) = &H65F710E8
        asm(13) = &HF7C30314
        asm(14) = &HE08AF075
        asm(15) = &H8A08E0C1
        asm(16) = &HD8E2ABC4
        asm(17) = &HC01B58F9
        asm(18) = &H5D5B5E5F
        asm(19) = &H10C2
    End If
    
    ' ************************************************************
    
    asmScale = CallWindowProc(asm(0), lpAsmBmpPara, rf, gf, BF)
End Function

' basScale
'
' AUFRUF: basScale(src, tgt, [rf:RotFaktor], _
'                 [gf:GrünFaktor], [bf:BlauFaktor])
'
' EIN:    bar:src Herkunftsdaten (ByteArray)
'         bar:tgt Zieldaten      (ByteArray)
'         lng:rf  red   factor   (default = 71)
'         lng:gf  green factor   (default = 707)
'         bol:bf  blue  factor   (default = 222)
'
' AUS:    log     Erfolg

Function basScale(src() As Byte, tgt() As Byte, _
    Optional rf As Long = 71, _
    Optional gf As Long = 707, _
    Optional BF As Long = 222) As Boolean
    
    Dim X1      As Long
    Dim Y1      As Long
    Dim N1      As Long
    
    For X1 = 1 To UBound(src, 1) Step 4
        For Y1 = 1 To UBound(src, 2)
            
            N1 = (src(X1 + 0, Y1) * _
            rf + src(X1 + 1, Y1) * _
            gf + src(X1 + 2, Y1) * BF) / 1000
            
            If N1 > 255 Then N1 = 255
            
            tgt(X1 + 0, Y1) = N1
            tgt(X1 + 1, Y1) = N1
            tgt(X1 + 2, Y1) = N1
        Next Y1
    Next X1
    
    basScale = True
End Function

'---- Ende Modul "asm_GrayScale" alias asm_GrayScale.bas ----
'------------ Ende Projektdatei prjGrayStyle.vbp ------------

Tipp-Kompatibilität:

Windows/VB-VersionWin32sWin95Win98WinMEWinNT4Win2000WinXP
VB4
VB5
VB6

Hat dieser Tipp auf Ihrem Betriebsystem und mit Ihrer VB-Version funktioniert?

Ja, funktioniert!

Nein, funktioniert nicht bei mir!

VB-Version:

Windows-Version:

Ihre Meinung  

Falls Sie Fragen zu diesem Artikel haben oder Ihre Erfahrung mit anderen Nutzern austauschen möchten, dann teilen Sie uns diese bitte in einem der unten vorhandenen Themen oder über einen neuen Beitrag mit. Hierzu können sie einfach einen Beitrag in einem zum Thema passenden Forum anlegen, welcher automatisch mit dieser Seite verknüpft wird.