notepad-plus-plus/lexilla/test/examples/smalltalk/ClassificationTable.st.folded
Christian Grasser 213e9135ba Update to scintilla 5.5.3 & Lexilla 5.4.1
Release 5.5.3 (https://www.scintilla.org/scintilla553.zip)

    Released 19 October 2024.
    On Win32 change direction of horizontal mouse wheel and touchpad scrolling to match other applications. Bug #2449.

Release 5.4.1 (https://www.scintilla.org/lexilla541.zip)

    Released 19 October 2024.
    Lexer added for Dart "dart". Pull request #265, Pull request #275.
    Lexer added for troff / nroff "troff". Pull request #264.
    Lexer added for Zig "zig". Pull request #267.
    C++: Fix crash for empty documentation comment keyword where '<' occurs at line end.
    F#: Include EOLs in the style range of SCE_FSHARP_COMMENTLINE. Stabilizes EOL detection when folding line comment groups. Issue #276.
    F#: Fix per-line folding in F# documents. Issue #277.
    HTML: Improve SGML/DTD lexing. Don't terminate SGML when > inside quoted string. Lex both [ and ] as SCE_H_SGML_DEFAULT. Nested sections handled instead of switching to SCE_H_SGML_ERROR. Issue #272.
    JavaScript: New SCE_HJ_TEMPLATELITERAL and SCE_HJA_TEMPLATELITERAL styles for template literals when lexer is hypertext, or xml. Issue #280.
    PHP: Fix failure to recognize PHP start "<?php' at end of document. Caused by not capping retrieval range at document end causing no text to be retrieved. Issue #269.
    Smalltalk: Fix scaled decimal numbers without decimal separator. Pull request #274.

Fix #15228, fix #15368, fix #15650, close #15717
2024-10-20 17:33:07 +02:00

53 lines
2.5 KiB
Plaintext

0 400 0 " File contains examples of all SCE_ST_* lexical states 0-16 "
0 400 0 " Smalltalk code from the lexer that generates the character classification table."
0 400 0 | lexTable classificationBlock charClasses |
0 400 0 charClasses := #(#DecDigit #Letter #Special #Upper #BinSel).
0 400 0 lexTable := ByteArray new: 128.
0 400 0 classificationBlock := [ :charClass :chars |
0 400 0 | flag |
0 400 0 flag := 1 bitShift: (charClasses indexOf: charClass) - 1.
0 400 0 chars do: [ :char | lexTable at: char codePoint + 1 put: ((lexTable at: char codePoint + 1) bitOr: flag)]].
0 400 0
0 400 0 classificationBlock
0 400 0 value: #DecDigit value: '0123456789';
0 400 0 value: #Letter value: '_abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ';
0 400 0 value: #Special value: '()[]{};.^:';
0 400 0 value: #BinSel value: '~@%&*-+=|\/,<>?!';
0 400 0 value: #Upper value: 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'.
0 400 0
0 400 0 ((String new: 500) streamContents: [ :stream |
0 400 0 stream crLf; nextPutAll: 'static int ClassificationTable[256] = {'.
0 400 0 lexTable keysAndValuesDo: [ :index :value |
0 400 0 ((index - 1) rem: 16) == 0 ifTrue: [
0 400 0 stream crLf; tab]
0 400 0 ifFalse: [
0 400 0 stream space].
0 400 0 stream print: value.
0 400 0 index ~= 256 ifTrue: [
0 400 0 stream nextPut: $,]].
0 400 0 stream crLf; nextPutAll: '};'; crLf.
0 400 0
0 400 0 charClasses keysAndValuesDo: [ :index :name |
0 400 0 stream
0 400 0 crLf;
0 400 0 nextPutAll: (
0 400 0 ('static inline bool is<1s>(unsigned char ch) {return (ch %< 0x80) && ((ClassificationTable[ch] & <2p>) != 0);}')
0 400 0 expandMacrosWith: name with: (1 bitShift: (index - 1)))
0 400 0 ]]) edit
0 400 0
0 400 0 " Some more syntax examples:
0 400 0 ^ is return (SCE_ST_RETURN)
0 400 0 true or false is bool (SCE_ST_BOOL)
0 400 0 self (SCE_ST_SELF)
0 400 0 super (SCE_ST_SUPER)
0 400 0 nil (SCE_ST_NIL)
0 400 0 "
0 400 0 foo
0 400 0 ^ Array with: 1 with: 2 with: false with: self with: super with: nil.
0 400 0
0 400 0 " Issue 274: A decimal separator is not required for scaled decimal numbers"
0 400 0 32.0s2
0 400 0 4.0e3
0 400 0 32s2
0 400 0 4e3
0 400 0