当前位置:编程学习 > VB >>

求助:VB语法高亮控件"rtbSyntax"怎么使用?

我把控件发上来,请知道用法的说一下,也可以发源码!本人万分感激....

        我使用的时候,在打开跟查找的时候提示:无效属性值!

请帮忙解决..   截图:
       
            

控件源码: 名称:rtbSyntax   跟RichTextBox1一样

Option Explicit

Const COMMENT = "'"

Const DELIMITER = vbTab & " ,(){}[]-+*%/='~!&|\<>?:;."

Const RESERVED As String = " And Call Case Const Dim Do Each Else ElseIf Empty End Eqv Erase Error Exit Explicit False For Function If Imp In Is Loop Mod Next Not Nothing Null On Option Or Private Public Randomize ReDim Resume Select Set Step Sub Then To True Until Wend While Xor "
Const FUNC_OBJ As String = " Anchor Array Asc Atn CBool CByte CCur CDate CDbl Chr CInt CLng Cos CreateObject CSng CStr Date DateAdd DateDiff DatePart DateSerial DateValue Day Dictionary Document Element Err Exp FileSystemObject  Filter Fix Int Form FormatCurrency FormatDateTime FormatNumber FormatPercent GetObject Hex History Hour InputBox InStr InstrRev IsArray IsDate IsEmpty IsNull IsNumeric IsObject Join LBound LCase Left Len Link LoadPicture Location Log LTrim RTrim Trim Mid Minute Month MonthName MsgBox Navigator Now Oct Replace Right Rnd Round ScriptEngine ScriptEngineBuildVersion ScriptEngineMajorVersion ScriptEngineMinorVersion Second Sgn Sin Space Split Sqr StrComp String StrReverse Tan Time TextStream TimeSerial TimeValue TypeName UBound UCase VarType Weekday WeekDayName Window Year "
Const KEYWORD_PAD As String = " "

Const RGB_COMMENT As String = "0,128,0"
Const RGB_STRING As String = "255,0,255"
Const RGB_RESERVED As String = "0,0,255"
Const RGB_FUNC_OBJ As String = "255,0,0"
Const RGB_DELIMITER As String = "0,0,0"
Const RGB_NORMAL As String = "0,0,0"

Enum SyntaxTypes
    ColorComment = 0
    ColorString = 1
    ColorReserved = 2
    ColorFuncObj = 3
    ColorDelimiter = 4
    ColorNormal = 5
End Enum --------------------编程问答-------------------- 接上:
Private mbInChange As Boolean
Private mrgbComment As Long
Private mrgbString As Long
Private mrgbReserved As Long
Private mrgbFuncObj As Long
Private mrgbDelimiter As Long
Private mrgbNormal As Long
Private Const WM_SETREDRAW = &HB
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private mlPrevSelStart As Long
Private mlCurSelStart As Long
Const m_def_ForeColor = 0
Const m_def_hWnd = 0
Dim m_ForeColor As Long
Dim m_hWnd As Long
Event Change() 'MappingInfo=rtb,rtb,-1,Change
Event Click() 'MappingInfo=rtb,rtb,-1,Click
Event DblClick() 'MappingInfo=rtb,rtb,-1,DblClick
Event KeyDown(KeyCode As Integer, Shift As Integer) 'MappingInfo=rtb,rtb,-1,KeyDown
Event KeyUp(KeyCode As Integer, Shift As Integer) 'MappingInfo=rtb,rtb,-1,KeyUp
Event KeyPress(KeyAscii As Integer) 'MappingInfo=rtb,rtb,-1,KeyPress
Event MouseDown(Button As Integer, Shift As Integer, x As Single, y As Single) 'MappingInfo=rtb,rtb,-1,MouseDown
Event MouseMove(Button As Integer, Shift As Integer, x As Single, y As Single) 'MappingInfo=rtb,rtb,-1,MouseMove
Event MouseUp(Button As Integer, Shift As Integer, x As Single, y As Single) 'MappingInfo=rtb,rtb,-1,MouseUp
Event SelChange() 'MappingInfo=rtb,rtb,-1,SelChange

Private Sub UserControl_Initialize()
    rtb.Top = 0
    rtb.Left = 0
    
    InitParser
    mlPrevSelStart = 0
End Sub

Private Sub InitParser()
    Dim vArr
    
    vArr = Split(RGB_COMMENT, ",")
    mrgbComment = RGB(vArr(0), vArr(1), vArr(2))
    
    vArr = Split(RGB_STRING, ",")
    mrgbString = RGB(vArr(0), vArr(1), vArr(2))
    
    vArr = Split(RGB_RESERVED, ",")
    mrgbReserved = RGB(vArr(0), vArr(1), vArr(2))
    
    vArr = Split(RGB_FUNC_OBJ, ",")
    mrgbFuncObj = RGB(vArr(0), vArr(1), vArr(2))
    
    vArr = Split(RGB_DELIMITER, ",")
    mrgbDelimiter = RGB(vArr(0), vArr(1), vArr(2))
    
    vArr = Split(RGB_NORMAL, ",")
    mrgbNormal = RGB(vArr(0), vArr(1), vArr(2))
    
End Sub

'
' Sub rtb_Change
' Determine the changed region and feed to the parser.
'
Private Sub rtb_Change()
    RaiseEvent Change
    
    If mbInChange = True Then
        ' change is being blocked or deferred
        GoTo ExitSub
    End If
    
    ' suppress change events generated during this change event
    '
    mbInChange = "True"
    
        
    Dim srtbText As String      ' working string
    ' add final cariage return so last line is processed
    srtbText = rtb.Text & vbCrLf
    
    ' preserve selection and restore at end
    '
    Dim lOrigSelStart As Long
    Dim lOrigSelLength As Long
    lOrigSelStart = rtb.SelStart
    lOrigSelLength = rtb.SelLength
    
    
    Dim lStartPos As Long
    Dim lEndPos As Long
    
    If mlPrevSelStart < rtb.SelStart Then
        lStartPos = mlPrevSelStart
        lEndPos = rtb.SelStart
    Else
        lStartPos = rtb.SelStart
        lEndPos = mlPrevSelStart
    End If
    
    
    If lStartPos > 1 Then
        ' set start position to beginning of line
        If InStrRev(srtbText, vbCrLf, lStartPos - 1) > 0 Then
            lStartPos = InStrRev(srtbText, vbCrLf, lStartPos - 1) + Len(vbCrLf) - 1
        Else
            lStartPos = 0
        End If
    Else
        lStartPos = 0
    End If
    
    ' set end position to end of line
    If InStr(lEndPos + 1, srtbText, vbCrLf) > 0 Then
        lEndPos = InStr(rtb.SelStart + 1, srtbText, vbCrLf) - 1
    Else
        lEndPos = Len(srtbText) - 1
    End If
    
    
    Dim x As Long
    
    'prevent textbox from repainting
    x = SendMessage(rtb.hWnd, WM_SETREDRAW, 0, 0)
    
    ' send affected text to the parser, along with its position in the
    ' RichTextBox
    If lStartPos <> lEndPos Then
        ParseLines Mid(srtbText, lStartPos + 1, lEndPos - lStartPos), rtb, lStartPos
    End If
    
    rtb.SelStart = lOrigSelStart
    rtb.SelLength = lOrigSelLength

    'allow texbox to repaint
    x = SendMessage(rtb.hWnd, WM_SETREDRAW, 1, 0)
    'force repaint
    rtb.Refresh
    
    mbInChange = False
    
ExitSub:
    
End Sub

Private Sub rtb_SelChange()
    RaiseEvent SelChange

    mlPrevSelStart = mlCurSelStart
    mlCurSelStart = rtb.SelStart
    

End Sub

Private Sub rtb_KeyDown(KeyCode As Integer, Shift As Integer)
    RaiseEvent KeyDown(KeyCode, Shift)

    If KeyCode = Asc(vbTab) Then  ' TAB key was pressed.
      ' Ignore the TAB key, so focus doesn't leave the control
      KeyCode = 0
      
      ' Replace selected text with the tab character
      rtb.SelText = vbTab
    End If


End Sub --------------------编程问答-------------------- 继续;
Public Sub HighlightRefresh()
    'prevent textbox from repainting
    Dim x As Long
    x = SendMessage(rtb.hWnd, WM_SETREDRAW, 0, 0)

    Dim lOrigSelStart As Long
    Dim lOrigSelLength As Long
    lOrigSelStart = rtb.SelStart
    lOrigSelLength = rtb.SelLength

    mlPrevSelStart = 0
    rtb.SelStart = Len(rtb.Text)
    rtb_Change
    rtb.SelStart = lOrigSelStart
    rtb.SelLength = lOrigSelStart

    'allow texbox to repaint
    x = SendMessage(rtb.hWnd, WM_SETREDRAW, 1, 0)
    'force repaint
    rtb.Refresh
End Sub

Private Sub ParseLines(ByVal s As String, rtb As RichTextBox, ByVal RTBPos As Long)
    Dim lStartPos As Long
    Dim lEndPos As Long
    
    lStartPos = 1
    
    s = s & vbCrLf
    lEndPos = InStr(lStartPos, s, vbCrLf)
    Do While lEndPos > 0
        ParseLine Mid(s, lStartPos, lEndPos - lStartPos), rtb, RTBPos + lStartPos - 1
        lStartPos = lEndPos + Len(vbCrLf)
        lEndPos = InStr(lStartPos, s, vbCrLf)
    Loop
    
        
        
End Sub

Private Sub ParseLine(ByVal s As String, rtb As RichTextBox, ByVal RTBPos As Long)
    'Debug.Print s
    
    Dim bInString As Boolean    ' are we in a quoted string?
    bInString = False
    
    Dim bInWord As Boolean      ' are we in a word? (not a string, comment,
                                ' or delimiter)
    bInWord = False
    
    Dim sCurString As String        ' the current set of characters
    Dim lCurStringStart As Long     '   - where it starts
    Dim sCurChar As String          ' the current character
    
    Dim i As Long
    
    For i = 1 To Len(s)
        sCurChar = Mid(s, i, 1)
        If sCurChar = COMMENT Then
            ' if comment character occurs within a quoted string, it doesn't
            ' count
            If Not bInString Then
                ' this is a comment. we are done with the line
                If bInWord Then
                    ' before we encounterd the comment we were processing a word
                    Highlight rtb, ParseWord(sCurString), lCurStringStart + RTBPos - 1, i - lCurStringStart
                    sCurString = ""
                    bInWord = False
                End If
            
                Highlight rtb, ColorComment, i + RTBPos - 1, Len(s) - i + 1
                GoTo ExitSub    ' rest of line is comment
            End If
        End If
        
        If sCurChar = """" Then
            ' if not already in a string, then this quote begins a string
            ' otherwise, we are in a string, and this quote ends it
            If bInString Then
                sCurString = sCurString & sCurChar
                Highlight rtb, ColorString, lCurStringStart + RTBPos - 1, i - lCurStringStart + 1
                sCurString = ""
                bInString = False
            Else
                If bInWord Then
                    ' before we encounterd the string we were processing a word
                    Highlight rtb, ParseWord(sCurString), lCurStringStart + RTBPos - 1, i - lCurStringStart
                    sCurString = ""
                    bInWord = False
                End If
                
                bInString = True
                sCurString = sCurChar
                lCurStringStart = i
            End If
            
            GoTo Next_i ' get next character
        End If
                
        If InStr(1, DELIMITER, sCurChar) > 0 Then
            If bInWord Then
                ' before we encounterd the delimiter we were processing a word
                Highlight rtb, ParseWord(sCurString), lCurStringStart + RTBPos - 1, i - lCurStringStart
                sCurString = ""
                bInWord = False
            End If
            
            Highlight rtb, ColorDelimiter, i + RTBPos - 1, 1
            GoTo Next_i
        End If
            
        If (Not bInWord) And (Not bInString) Then
            bInWord = True
            sCurString = sCurChar
            lCurStringStart = i
            
            GoTo Next_i ' get next character
        End If
            
        ' add current character to the "word" we are in the middle of
        sCurString = sCurString & sCurChar
Next_i:     ' VB style continue
    Next
    
    If bInString Then
        ' before we encounterd the end of the line we were processing a string
        Highlight rtb, ColorString, lCurStringStart + RTBPos - 1, i - lCurStringStart
    ElseIf bInWord Then
        ' before we encounterd the end of the line we were processing a word
        Highlight rtb, ParseWord(sCurString), lCurStringStart + RTBPos - 1, i - lCurStringStart
    End If

ExitSub:
    Exit Sub
End Sub --------------------编程问答-------------------- 在继续:
Private Function ParseWord(ByVal Word As String) As SyntaxTypes
    If InStr(1, RESERVED, KEYWORD_PAD & Word & KEYWORD_PAD, vbTextCompare) > 0 Then
        ParseWord = ColorReserved
    ElseIf InStr(1, FUNC_OBJ, KEYWORD_PAD & Word & KEYWORD_PAD, vbTextCompare) > 0 Then
        ParseWord = ColorFuncObj
    Else
        ParseWord = ColorNormal
    End If
End Function

Private Sub Highlight(rtb As RichTextBox, SyntaxType As SyntaxTypes, StartPos As Long, Length As Long)
        rtb.SelStart = StartPos
        rtb.SelLength = Length
    
    Select Case SyntaxType
        Case SyntaxTypes.ColorComment
            rtb.SelColor = mrgbComment
        Case SyntaxTypes.ColorString
            rtb.SelColor = mrgbString
        Case SyntaxTypes.ColorReserved
            rtb.SelColor = mrgbReserved
        Case SyntaxTypes.ColorFuncObj
            rtb.SelColor = mrgbFuncObj
        Case SyntaxTypes.ColorDelimiter
            rtb.SelColor = mrgbDelimiter
        Case Else
            rtb.SelColor = mrgbNormal
    End Select

End Sub

Private Sub UserControl_Resize()
    rtb.Width = UserControl.ScaleWidth
    rtb.Height = UserControl.ScaleHeight
End Sub


Public Property Get AutoVerbMenu() As Boolean
    AutoVerbMenu = rtb.AutoVerbMenu
End Property

Public Property Let AutoVerbMenu(ByVal New_AutoVerbMenu As Boolean)
    rtb.AutoVerbMenu() = New_AutoVerbMenu
    PropertyChanged "AutoVerbMenu"
End Property

Public Property Get BackColor() As OLE_COLOR
    BackColor = rtb.BackColor
End Property

Public Property Let BackColor(ByVal New_BackColor As OLE_COLOR)
    rtb.BackColor() = New_BackColor
    PropertyChanged "BackColor"
End Property

Public Property Get ForeColor() As Long
    ForeColor = m_ForeColor
End Property

Public Property Let ForeColor(ByVal New_ForeColor As Long)
    m_ForeColor = New_ForeColor
    PropertyChanged "ForeColor"
End Property

Public Property Get BorderStyle() As BorderStyleConstants
    BorderStyle = rtb.BorderStyle
End Property

Public Property Let BorderStyle(ByVal New_BorderStyle As BorderStyleConstants)
    rtb.BorderStyle() = New_BorderStyle
    PropertyChanged "BorderStyle"
End Property

Public Property Get BulletIndent() As Single
    BulletIndent = rtb.BulletIndent
End Property

Public Property Let BulletIndent(ByVal New_BulletIndent As Single)
    rtb.BulletIndent() = New_BulletIndent
    PropertyChanged "BulletIndent"
End Property

Public Property Get Enabled() As Boolean
    Enabled = rtb.Enabled
End Property

Public Property Let Enabled(ByVal New_Enabled As Boolean)
    rtb.Enabled() = New_Enabled
    PropertyChanged "Enabled"
End Property

Public Property Get FileName() As String
    FileName = rtb.FileName
End Property

Public Property Let FileName(ByVal New_FileName As String)
    rtb.FileName() = New_FileName
    
    PropertyChanged "FileName"
End Property

Public Property Get Font() As Font
    Set Font = rtb.Font
End Property

Public Property Set Font(ByVal New_Font As Font)
    Set rtb.Font = New_Font
    PropertyChanged "Font"
End Property

Public Property Get HideSelection() As Boolean
    HideSelection = rtb.HideSelection
End Property

Public Property Let HideSelection(ByVal New_HideSelection As Boolean)
    rtb.HideSelection() = New_HideSelection
    PropertyChanged "HideSelection"
End Property

Public Property Get hWnd() As Long
    hWnd = m_hWnd
End Property

Public Property Let hWnd(ByVal New_hWnd As Long)
    m_hWnd = New_hWnd
    PropertyChanged "hWnd"
End Property

Public Property Get Locked() As Boolean
    Locked = rtb.Locked
End Property

Public Property Let Locked(ByVal New_Locked As Boolean)
    rtb.Locked() = New_Locked
    PropertyChanged "Locked"
End Property

Public Property Get MaxLength() As Long
    MaxLength = rtb.MaxLength
End Property

Public Property Let MaxLength(ByVal New_MaxLength As Long)
    rtb.MaxLength() = New_MaxLength
    PropertyChanged "MaxLength"
End Property

Public Property Get MouseIcon() As Picture
    Set MouseIcon = rtb.MouseIcon
End Property

Public Property Set MouseIcon(ByVal New_MouseIcon As Picture)
    Set rtb.MouseIcon = New_MouseIcon
    PropertyChanged "MouseIcon"
End Property

Public Property Get MousePointer() As MousePointerConstants
    MousePointer = rtb.MousePointer
End Property

Public Property Let MousePointer(ByVal New_MousePointer As MousePointerConstants)
    rtb.MousePointer() = New_MousePointer
    PropertyChanged "MousePointer"
End Property

Public Property Get RightMargin() As Single
    RightMargin = rtb.RightMargin
End Property

Public Property Let RightMargin(ByVal New_RightMargin As Single)
    rtb.RightMargin() = New_RightMargin
    PropertyChanged "RightMargin"
End Property

Public Property Get Text() As String
    Text = rtb.Text
End Property

Public Property Let Text(ByVal New_Text As String)
    mbInChange = True
    rtb.Text() = New_Text
    mbInChange = False
    HighlightRefresh
    
    PropertyChanged "Text"
End Property

Public Function Find(ByVal bstrString As String, Optional ByVal vStart As Variant, Optional ByVal vEnd As Variant, Optional ByVal vOptions As Variant) As Long
    Find = rtb.Find(bstrString, vStart, vEnd, vOptions)
End Function

Public Function GetLineFromChar(ByVal lChar As Long) As Long
    GetLineFromChar = rtb.GetLineFromChar(lChar)
End Function

Public Sub LoadFile(ByVal bstrFilename As String, Optional ByVal vFileType As Variant)
    rtb.LoadFile bstrFilename, vFileType
End Sub

Public Sub Refresh()
    rtb.Refresh
End Sub

Public Sub SaveFile(ByVal bstrFilename As String, Optional ByVal vFlags As Variant)
    rtb.SaveFile bstrFilename, vFlags
End Sub

Public Sub SelPrint(ByVal lHDC As Long, Optional ByVal vStartDoc As Variant)
    rtb.SelPrint lHDC, vStartDoc
End Sub

Public Sub Span(ByVal bstrCharacterSet As String, Optional ByVal vForward As Variant, Optional ByVal vNegate As Variant)
    rtb.Span bstrCharacterSet, vForward, vNegate
End Sub

Public Sub UpTo(ByVal bstrCharacterSet As String, Optional ByVal vForward As Variant, Optional ByVal vNegate As Variant)
    rtb.UpTo bstrCharacterSet, vForward, vNegate
End Sub

Private Sub rtb_Click()
    RaiseEvent Click
End Sub

Private Sub rtb_DblClick()
    RaiseEvent DblClick
End Sub

Private Sub rtb_KeyUp(KeyCode As Integer, Shift As Integer)
    RaiseEvent KeyUp(KeyCode, Shift)
End Sub

Private Sub rtb_KeyPress(KeyAscii As Integer)
    RaiseEvent KeyPress(KeyAscii)
End Sub

Private Sub rtb_MouseDown(Button As Integer, Shift As Integer, x As Single, y As Single)
    RaiseEvent MouseDown(Button, Shift, x, y)
End Sub

Private Sub rtb_MouseMove(Button As Integer, Shift As Integer, x As Single, y As Single)
    RaiseEvent MouseMove(Button, Shift, x, y)
End Sub

Private Sub rtb_MouseUp(Button As Integer, Shift As Integer, x As Single, y As Single)
    RaiseEvent MouseUp(Button, Shift, x, y)
End Sub

'Initialize Properties for User Control
Private Sub UserControl_InitProperties()
    m_ForeColor = m_def_ForeColor
    m_hWnd = m_def_hWnd
End Sub
--------------------编程问答-------------------- --------------------编程问答-------------------- 还有:
Private Sub UserControl_ReadProperties(PropBag As PropertyBag)
    ' prevent parsing while file is loading
    mbInChange = True
    
    rtb.AutoVerbMenu = PropBag.ReadProperty("AutoVerbMenu", False)
    rtb.BackColor = PropBag.ReadProperty("BackColor", &H80000005)
    m_ForeColor = PropBag.ReadProperty("ForeColor", m_def_ForeColor)
    rtb.BorderStyle = PropBag.ReadProperty("BorderStyle", 1)
    rtb.BulletIndent = PropBag.ReadProperty("BulletIndent", 0)
    rtb.Enabled = PropBag.ReadProperty("Enabled", True)
    rtb.FileName = PropBag.ReadProperty("FileName", "")
    Set rtb.Font = PropBag.ReadProperty("Font", Ambient.Font)
    rtb.HideSelection = PropBag.ReadProperty("HideSelection", True)
    m_hWnd = PropBag.ReadProperty("hWnd", m_def_hWnd)
    rtb.Locked = PropBag.ReadProperty("Locked", False)
    rtb.MaxLength = PropBag.ReadProperty("MaxLength", 0)
    Set MouseIcon = PropBag.ReadProperty("MouseIcon", Nothing)
    rtb.MousePointer = PropBag.ReadProperty("MousePointer", 0)
    rtb.RightMargin = PropBag.ReadProperty("RightMargin", 0)
    rtb.Text = PropBag.ReadProperty("Text", "")
    
    mbInChange = False
    HighlightRefresh
    
End Sub

Private Sub UserControl_WriteProperties(PropBag As PropertyBag)

    Call PropBag.WriteProperty("AutoVerbMenu", rtb.AutoVerbMenu, False)
    Call PropBag.WriteProperty("BackColor", rtb.BackColor, &H80000005)
    Call PropBag.WriteProperty("ForeColor", m_ForeColor, m_def_ForeColor)
    Call PropBag.WriteProperty("BorderStyle", rtb.BorderStyle, 1)
    Call PropBag.WriteProperty("BulletIndent", rtb.BulletIndent, 0)
    Call PropBag.WriteProperty("Enabled", rtb.Enabled, True)
    Call PropBag.WriteProperty("FileName", rtb.FileName, "")
    Call PropBag.WriteProperty("Font", rtb.Font, Ambient.Font)
    Call PropBag.WriteProperty("HideSelection", rtb.HideSelection, True)
    Call PropBag.WriteProperty("hWnd", m_hWnd, m_def_hWnd)
    Call PropBag.WriteProperty("Locked", rtb.Locked, False)
    Call PropBag.WriteProperty("MaxLength", rtb.MaxLength, 0)
    Call PropBag.WriteProperty("MouseIcon", MouseIcon, Nothing)
    Call PropBag.WriteProperty("MousePointer", rtb.MousePointer, 0)
    Call PropBag.WriteProperty("RightMargin", rtb.RightMargin, 0)
    Call PropBag.WriteProperty("Text", rtb.Text, "")
End Sub

Public Property Get SelAlignment() As SelAlignmentConstants
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelAlignment = rtb.SelAlignment
End Property

Public Property Let SelAlignment(ByVal New_SelAlignment As SelAlignmentConstants)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelAlignment = New_SelAlignment
End Property

Public Property Get SelBold() As Boolean
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelBold = rtb.SelBold
End Property

Public Property Let SelBold(ByVal New_SelBold As Boolean)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelBold = New_SelBold
End Property

Public Property Get SelItalic() As Boolean
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelItalic = rtb.SelItalic
End Property

Public Property Let SelItalic(ByVal New_SelItalic As Boolean)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelItalic = New_SelItalic
End Property

Public Property Get SelStrikethru() As Boolean
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelStrikethru = rtb.SelStrikethru
End Property

Public Property Let SelStrikethru(ByVal New_SelStrikethru As Boolean)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelStrikethru = New_SelStrikethru
End Property

Public Property Get SelUnderline() As Boolean
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelUnderline = rtb.SelUnderline
End Property

Public Property Let SelUnderline(ByVal New_SelUnderline As Boolean)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelUnderline = New_SelUnderline
End Property

Public Property Get SelBullet() As Variant
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelBullet = rtb.SelBullet
End Property

Public Property Let SelBullet(ByVal New_SelBullet As Variant)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelBullet = New_SelBullet
End Property

Public Property Get SelCharOffset() As Variant
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelCharOffset = rtb.SelCharOffset
End Property

Public Property Let SelCharOffset(ByVal New_SelCharOffset As Variant)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelCharOffset = New_SelCharOffset
End Property

Public Property Get SelRTF() As String
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelRTF = rtb.SelRTF
End Property

Public Property Let SelRTF(ByVal New_SelRTF As String)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelRTF = New_SelRTF
End Property

Public Property Get SelTabCount() As Integer
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelTabCount = rtb.SelTabCount
End Property

Public Property Let SelTabCount(ByVal New_SelTabCount As Integer)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelTabCount = New_SelTabCount
End Property

Public Property Get SelTabs(Index As Integer) As Integer
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelTabs = rtb.SelTabs(Index)
End Property

Public Property Let SelTabs(Index As Integer, ByVal New_SelTabs As Integer)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelTabs(Index) = New_SelTabs
End Property

Public Property Get SelColor() As Variant
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelColor = rtb.SelColor
End Property

Public Property Let SelColor(ByVal New_SelColor As Variant)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelColor = New_SelColor
End Property

Public Property Get SelHangingIndent() As Integer
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelHangingIndent = rtb.SelHangingIndent
End Property

Public Property Let SelHangingIndent(ByVal New_SelHangingIndent As Integer)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelHangingIndent = New_SelHangingIndent
End Property --------------------编程问答-------------------- 结束:
Public Property Get SelIndent() As Integer
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelIndent = rtb.SelIndent
End Property

Public Property Let SelIndent(ByVal New_SelIndent As Integer)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelIndent = New_SelIndent
End Property

Public Property Get SelRightIndent() As Integer
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelRightIndent = rtb.SelRightIndent
End Property

Public Property Let SelRightIndent(ByVal New_SelRightIndent As Integer)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelRightIndent = New_SelRightIndent
End Property

Public Property Get SelLength() As Long
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelLength = rtb.SelLength
End Property

Public Property Let SelLength(ByVal New_SelLength As Long)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelLength = New_SelLength
End Property

Public Property Get SelStart() As Long
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelStart = rtb.SelStart
End Property

Public Property Let SelStart(ByVal New_SelStart As Long)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelStart = New_SelStart
End Property

Public Property Get SelText() As String
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelText = rtb.SelText
End Property

Public Property Let SelText(ByVal New_SelText As String)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelText = New_SelText
End Property

Public Property Get SelProtected() As Variant
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    
    SelProtected = rtb.SelProtected
End Property

Public Property Let SelProtected(ByVal New_SelProtected As Variant)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
    
    rtb.SelProtected = New_SelProtected
End Property

Public Property Get TextRTF() As String
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 394
    End If
    TextRTF = rtb.TextRTF
End Property

Public Property Let TextRTF(ByVal New_TextRTF As String)
    ' prevent display in property browser
    If Ambient.UserMode = False Then
        Err.Raise 383
    End If
        
    mbInChange = True
    rtb.TextRTF = New_TextRTF
    mbInChange = False
    
    HighlightRefresh

End Property --------------------编程问答-------------------- 代码太多了,给个控件下载地址:http://dldx.csdn.net/fd.php?i=464427582081822&s=ea443a02774d7cf30856c0274b406606
知道怎么用的帮忙解决一下,谢谢!!
补充:VB ,  基础类
CopyRight © 2012 站长网 编程知识问答 www.zzzyk.com All Rights Reserved
部份技术文章来自网络,