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