Guidance
指路人
g.yi.org
software / rapidq / examples / gui / Edit & Richedit / syntax / syntax.bas

Register 
注册
Search 搜索
首页 
Home Home
Software
Upload

  
' Simple Syntax Hilighting example for Rapid-Q by William Yu
'
' QREdit        - Extension of QRichEdit with automatic syntax hilighting
'                 Not very complete, but you can handle all the special cases.
'
' NEW PROPERTIES:
'   HiLighColor - Color to use for hilighting keywords
'
' NEW METHODS:
'   AddSyntaxes - Add any keywords you want hilighted
'       HiLight - Call first time whenever you load a file, or add new lines
'
' There are actually 2 separate ways of doing this, the hard way, and the
' easy way.  The hard way is to learn RTF and create your own RTF document
' programmically. It's definitely more work than the easy way, which I'll
' demonstrate in this example.
' I've decided to incorporate this into a component for easy reuse.

     $APPTYPE GUI
     $TYPECHECK ON
     $INCLUDE "RAPIDQ.INC"

     TYPE QREdit EXTENDS QRICHEDIT
      RichFont AS QFONT
      Syntaxes(100) AS STRING       '-- Better way could be to use a ListBox
      MaxSyntax AS INTEGER
      HiLightColor AS INTEGER

      SUB HiLight
  '-- HiLight first time, call this whenever you insert line(s), or you
  '-- load a file.

       DIM TempStart AS INTEGER
       DIM I AS INTEGER, N AS INTEGER

       WITH QREdit
        TempStart = .SelStart
        .SelStart = 0
        .SelLength = LEN(.Text)
        .SelAttributes = .RichFont
        FOR I = 1 TO .MaxSyntax
         N = INSTR(UCASE$(.Text), UCASE$(.Syntaxes(I)))-1
         WHILE N >= 0
          .SelStart = N
          .RichFont.AddStyles(fsBold)
          .RichFont.COLOR = .HiLightColor
          .SelLength = LEN(.Syntaxes(I))
          .SelAttributes = .RichFont
          N = INSTR(N+.SelLength, UCASE$(.Text), UCASE$(QREdit.Syntaxes(I)))-1
         WEND
         .SelLength = 0
         .RichFont.DelStyles(fsBold)
         .RichFont.COLOR = 0
         .Font = .RichFont
         .SelStart = TempStart
        NEXT I
       END WITH
      END SUB

      SUBI AddSyntaxes(...)
       DIM I AS INTEGER

       WITH QREdit
        FOR I = 1 TO PARAMSTRCOUNT
         .Syntaxes(I+.MaxSyntax) = PARAMSTR$(I)
        NEXT
        .MaxSyntax = .MaxSyntax + PARAMSTRCOUNT
       END WITH
      END SUBI

      EVENT OnKeyUp (Key AS WORD, Shift AS INTEGER)
    '' Don't want to re-hilight everything, try to isolate a keyword
    '' If you type too fast, this event might be skipped :)
    '' Also beware when the user splits up two words with a space,
    '' that condition isn't handled here.

       DIM I AS INTEGER, EndStr AS INTEGER, StartStr AS INTEGER
       DIM TempStart AS INTEGER, N AS INTEGER
       DIM Token AS STRING
       DIM T1 AS INTEGER, T2 AS INTEGER

       T1 = QREdit.SelStart
       T2 = QREdit.SelLength

       IF Key < 46 AND Key <> 8 THEN     '' Ignore arrows, pageup/down, etc.
        EXIT EVENT
       END IF

       WITH QREdit
      '' Isolate a token, separated by a space (but that's not always the case)
        FOR I = .SelStart TO LEN(.Text)
         IF MID$(.Text, I, 1) = " " OR MID$(.Text, I, 1) = CHR$(13) OR MID$(.Text, I, 1) = CHR$(10) THEN
          EXIT FOR
         END IF
        NEXT I
        EndStr = I
        FOR I = .SelStart TO 1 STEP -1
         IF MID$(.Text, I, 1) = " " OR MID$(.Text, I, 1) = CHR$(10) OR MID$(.Text, I, 1) = CHR$(13) THEN
          EXIT FOR
         END IF
        NEXT I
        StartStr = I+1
        Token = RTRIM$(LTRIM$(MID$(.Text, StartStr, EndStr - StartStr)))

        TempStart = .SelStart
        .SelStart = StartStr-1
        .SelLength = LEN(Token)
        .SelAttributes = .RichFont
        FOR I = 1 TO .MaxSyntax
         IF UCASE$(Token) = UCASE$(.Syntaxes(I)) THEN
          .SelStart = StartStr-1
          .RichFont.AddStyles(fsBold)
          .RichFont.COLOR = .HiLightColor
          .SelLength = LEN(.Syntaxes(I))
          .SelAttributes = .RichFont
         END IF
        NEXT I
        .SelLength = 0
        .SelStart = TempStart
        .RichFont.DelStyles(fsBold)
        .RichFont.COLOR = 0
        .Font = .RichFont
       END WITH

       QREdit.SelStart = T1
       QREdit.SelLength= T2
      END EVENT

      CONSTRUCTOR
       PlainText = True
       RichFont.Name = "Courier"
       MaxSyntax = 0
       HiLightColor = &HAA0000
       Font = QREdit.RichFont
      END CONSTRUCTOR
     END TYPE


'-- Test Component

     CREATE Form AS QFORM
      CREATE RichEdit AS QREdit
       Align = alClient
       WordWrap = False
       Clear
       AddSyntaxes("PRINT", "CLS", "LOCATE", "END", "COLOR", "IF", "THEN", "ELSE")
       AddStrings("'-- Syntax Hilighting", "", _
        "10 CLS", _
        "20 PRINT "+CHR$(34)+"Hello World!"+CHR$(34), _
        "30 LOCATE 10,10", _
        "40 PRINT 1+2+3", _
        "50 IF RAPIDQ = GREAT THEN", _
        "60   PRINT "+CHR$(34)+"Oh yeah!"+CHR$(34), _
        "70 ELSE", _
        "80   END", _
        "90 END IF")
    'HiLightColor = &H0000FF
       HiLight
      END CREATE
      CAPTION = "Syntax hilighting"
      Center
      SHOWMODAL
     END CREATE
掌柜推荐
 
 
¥1,380.00 ·
 
 
¥1,450.00 ·
 
 
¥477.00 ·
 
 
¥264.00 ·
 
 
¥1,280.00 ·
 
 
¥489.00 ·
© Mon 2024-11-25  Guidance Laboratory Inc.
Email:webmaster1g.yi.org Hits:0 Last modified:1999-12-09 09:49:14