📄 t-gen-regularexpressionnodes.st
字号:
self firstChar asInteger to: self lastChar asInteger do: [:ascii | childNodes add: (self makeCharNodeFor: (Character value: ascii))]! !
RegularExpressionNode subclass: #UnaryRegExprNode
instanceVariableNames: 'onlyChild '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
UnaryRegExprNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a unary regular expression.'!
!UnaryRegExprNode methodsFor: 'state accessing'!
onlyChild
^onlyChild!
onlyChild: argument
onlyChild := argument! !
!UnaryRegExprNode methodsFor: 'traversing'!
childrenDo: aBlock
"Evaluate aBlock for each of my children."
aBlock value: self onlyChild!
updateChildrenUsing: aBlock
"Replace my children according to the value of aBlock."
self onlyChild: (aBlock value: self onlyChild)! !
!UnaryRegExprNode methodsFor: 'building parse trees'!
addChildrenInitial: anOrderedCollection
anOrderedCollection size = 1
ifTrue: [self onlyChild: anOrderedCollection removeFirst]
ifFalse: [self error: 'wrong number of children']! !
!UnaryRegExprNode methodsFor: 'transforming'!
needsTransforming
^true! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
UnaryRegExprNode class
instanceVariableNames: ''!
!UnaryRegExprNode class methodsFor: 'instance creation'!
onlyChild: arg1
| newMe |
newMe := self new.
newMe onlyChild: arg1.
^newMe! !
UnaryRegExprNode subclass: #OptionalNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
OptionalNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent the regular expression ''{expr}'' which denotes ''expr | <epsilon>''.'!
!OptionalNode methodsFor: 'printing'!
printOn: aStream
aStream nextPut: $(.
self onlyChild printOn: aStream.
aStream nextPutAll: ')?'! !
!OptionalNode methodsFor: 'converting'!
asPureRegExpr
"Answer a new version of the receiver consisting of only characters,
concatenations, alternations, and (star) closures."
^self alternationNodeClass children: (OrderedChildren with: self onlyChild asPureRegExpr with: self epsilonNodeClass new)! !
!OptionalNode methodsFor: 'transforming'!
transformUsing: lhsNames withLHS: lhsNode alpha: alphaNodes gamma: gammaNodes
"Transform productions of the form 'A -> alpha beta? gamma'
into 'A -> alpha B', 'B -> beta B', and 'B -> gamma'."
| newProds newLHS |
newProds := OrderedCollection new.
newLHS := self newNonterminalFrom: lhsNode excluding: lhsNames.
newProds add: (self createNewProductionWithLHS: lhsNode andRHS: (alphaNodes addLast: newLHS; yourself)).
newProds add: (self createNewProductionWithLHS: newLHS andRHS: ((gammaNodes copy) addFirst: self onlyChild; yourself)).
newProds add: (self createNewProductionWithLHS: newLHS andRHS: gammaNodes copy).
^newProds! !
BinaryRegExprNode subclass: #ListNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
ListNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am an instance of the regular expression ''a list b'' which is equivalent to a(ba)*.'!
!ListNode methodsFor: 'printing'!
printOn: aStream
aStream nextPut: $(.
self leftChild printOn: aStream.
aStream nextPutAll: ' ^ '.
self rightChild printOn: aStream.
aStream nextPut: $)! !
!ListNode methodsFor: 'transforming'!
needsTransforming
^true!
transformUsing: lhsNames withLHS: lhsNode alpha: alphaNodes gamma: gammaNodes
"Transform productions of the form 'A -> alpha beta1 list beta2 gamma'
into 'A -> alpha B', 'B -> beta1 gamma', and 'B -> beta1 beta2 B'."
| newProds newLHS |
newProds := OrderedCollection new.
newLHS := self newNonterminalFrom: lhsNode excluding: lhsNames.
newProds add: (self createNewProductionWithLHS: lhsNode andRHS: (alphaNodes addLast: newLHS; yourself)).
newProds add: (self createNewProductionWithLHS: newLHS andRHS: (gammaNodes addFirst: self leftChild copy; yourself)).
newProds add: (self createNewProductionWithLHS: newLHS andRHS: (OrderedCollection
with: self leftChild copy
with: self rightChild copy
with: newLHS)).
^newProds! !
RegularExpressionNode subclass: #CharacterNode
instanceVariableNames: 'charSpec '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
CharacterNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a atomic character of a regular expression.
Instance Variables:
charSpec <String> - contains the character atom specification for this node (different types of specifications are represented by subclasses).'!
!CharacterNode methodsFor: 'state accessing'!
charSpec
^charSpec!
charSpec: argument
charSpec := argument! !
!CharacterNode methodsFor: 'building parse trees'!
setAttribute: value
self charSpec: value! !
!CharacterNode methodsFor: 'printing'!
printOn: aStream
self charSpec printOn: aStream! !
!CharacterNode methodsFor: 'traversing'!
addNonemptyLeavesTo: aSet
aSet add: self myChar! !
!CharacterNode methodsFor: 'converting'!
addCharsTo: aCollection
"Add each character in my range to aCollection."
aCollection add: self myChar!
addPureCharNodesTo: childNodes
childNodes add: self!
asFSAStartingAt: startState endingAt: finalState
startState goto: finalState on: self myChar! !
!CharacterNode methodsFor: 'accessing'!
asInteger
^self myChar asInteger!
myChar
"Answer the Character represented by the receiver."
self charSpec size = 1
ifTrue: [^self charSpec first]
ifFalse: [self error: 'Only single character regular expressions atoms are currently supported.']! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
CharacterNode class
instanceVariableNames: ''!
!CharacterNode class methodsFor: 'instance creation'!
charSpec: arg1
| newMe |
newMe := self new.
newMe charSpec: arg1.
^newMe! !
CharacterNode subclass: #HexadecimalCharNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
HexadecimalCharNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a atomic character of a regular expression. I am specified by a String of the form ''\xHH'' where each H is a hexadecimal digit (0-9, a-f or A-F) and HH is my corresponding ASCII value.
'!
!HexadecimalCharNode methodsFor: 'accessing'!
myChar
"Answer the Character represented by the receiver.
The spec is of the form '\xHH'."
| spec |
spec := self charSpec.
(spec size = 4 and: [spec first = $\ and: [(spec at: 2)
= $x]])
ifTrue: [^Character value: ('16r' , (spec copyFrom: 3 to: 4)) asNumber]
ifFalse: [self error: 'Hexadecimal character specifications must be of the form ''\xHH''.']! !
CharacterNode subclass: #OctalCharNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
OctalCharNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a atomic character of a regular expression. I am specified by a String of the form ''\oOOO'' where each O is a octal digit (0-7) and OOO is my corresponding ASCII value.
'!
!OctalCharNode methodsFor: 'accessing'!
myChar
"Answer the Character represented by the receiver.
The spec is of the form '\oOOO'."
| spec |
spec := self charSpec.
(spec size = 5 and: [spec first = $\ and: [(spec at: 2)
= $o]])
ifTrue: [^Character value: ('8r' , (spec copyFrom: 3 to: 5)) asNumber]
ifFalse: [self error: 'Octal character specifications must be of the form ''\oOOO''.']! !
CharacterNode subclass: #DecimalCharNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
DecimalCharNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a atomic character of a regular expression. I am specified by a String of the form ''\ddd'' where each d is a decimal digit and ddd is my corresponding ASCII value.
'!
!DecimalCharNode methodsFor: 'accessing'!
myChar
"Answer the Character represented by the receiver.
The spec is of the form '\ddd'."
| spec |
spec := self charSpec.
(spec size = 4 and: [spec first = $\])
ifTrue: [^Character value: (spec copyFrom: 2 to: 4) asNumber]
ifFalse: [self error: 'Decimal character specifications must be of the form ''\ddd''.']! !
CharacterNode subclass: #EscapedCharNode
instanceVariableNames: ''
classVariableNames: 'SpecialCharMap '
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
EscapedCharNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a atomic character of a regular expression. I am specified by a String of the form ''\c'' where each c is some character. Normally, the character I represent is just c, however, some specifications have special meanings (see comment in class initialization method).'!
!EscapedCharNode methodsFor: 'accessing'!
myChar
"Answer the Character represented by the receiver.
The spec is of the form '\c' where some c's are special (see class comment)."
| spec char |
spec := self charSpec.
(spec size = 2 and: [spec first = $\])
ifTrue:
[char := spec last.
^self specialChars at: char ifAbsent: [char]]
ifFalse: [self error: 'Escaped character specifications must be of the form ''\c''.']!
specialChars
^SpecialCharMap! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
EscapedCharNode class
instanceVariableNames: ''!
!EscapedCharNode class methodsFor: 'initialization'!
initialize
"The following characters are special:
spec ascii character
---- ---- --------
\0 0 null
\b 8 backspace
\t 9 horizontal tab
\n 10 linefeed (UNIX newline \n)
\f 12 form feed
\r 13 carriage return (Smalltalk cr)
\e 27 escape
\s 32 space
\d 127 delete"
"EscapedCharNode initialize"
| dict |
dict := Dictionary new.
dict
at: $0 put: (Character value: 0);
at: $b put: (Character value: 8);
at: $t put: (Character value: 9);
at: $n put: (Character value: 10);
at: $f put: (Character value: 12);
at: $r put: (Character value: 13);
at: $e put: (Character value: 27);
at: $s put: (Character value: 32);
at: $d put: (Character value: 127).
SpecialCharMap := dict! !
RegularExpressionNode subclass: #EnnaryRegExprNode
instanceVariableNames: 'children '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Regular Expression Nodes'!
EnnaryRegExprNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent an n-ary regular expression.'!
!EnnaryRegExprNode methodsFor: 'state accessing'!
children
^children!
children: argument
children := argument! !
!EnnaryRegExprNode methodsFor: 'traversing'!
childrenDo: aBlock
"Evaluate aBlock for each of my children."
self children do: aBlock!
updateChildrenUsing: aBlock
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -