Skip to content

Instantly share code, notes, and snippets.

@smarr
Created July 28, 2017 14:49
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save smarr/46a26570f63e9b00954055b779437edb to your computer and use it in GitHub Desktop.
Save smarr/46a26570f63e9b00954055b779437edb to your computer and use it in GitHub Desktop.
Newspeak Parser Incompatibilities
diff -r 38a47c705f1a Collections.ns
--- a/Collections.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/Collections.ns Fri Jul 28 16:48:38 2017 +0200
@@ -49,7 +49,7 @@
binarySearchFor: el <EL>
between: start <Integer>
and: end <Integer>
-toCompare: compare <[:EL def:EL| Boolean]>
+toCompare: compare <[:EL def :EL| Boolean]>
^<Int>
= (
(* {where CONSTRAINER <EL> is returnType of #anElement message of receiverType} *)
@@ -74,7 +74,7 @@
)
public binarySearchFor: el <EL>
-toCompare: compare <[:EL def:EL| Boolean]>
+toCompare: compare <[:EL def :EL| Boolean]>
^ <Integer>
= (
#BOGUS. (* Remove me. *)
@@ -365,7 +365,7 @@
public isSequenceable = (
^true
)
-isSortedBy: compare <[:E:E| Boolean]> ^<Boolean> = (
+isSortedBy: compare <[:E :E| Boolean]> ^<Boolean> = (
(* Returns true if the receiver is in sorted order, using the specified comparison *)
@@ -807,7 +807,7 @@
^SortedList(* [Object] *) withAll: self
)
-public asSortedList: sortPredicate <[:E:EX | Boolean]> ^<SortedList[EX]> = (
+public asSortedList: sortPredicate <[:E :EX | Boolean]> ^<SortedList[EX]> = (
(* { where EX is arg 1 of #value:value: message of arg 1 } *)
(* Return a new sorted collection ordered by the given sortPredicate. Note that Magnitude
supports the defaultSort message for convenience, so that for example if you have a collection
@@ -950,7 +950,7 @@
^self reduce: reduceFn ifEmpty: [Error signal: 'Cannot reduce an empty collection' ]
)
-public reduce: reduceFn <[:RE def:RE| RE]> ifEmpty: onEmpty <[X def]> ^<RE | X> = (
+public reduce: reduceFn <[:RE def :RE| RE]> ifEmpty: onEmpty <[X def]> ^<RE | X> = (
(* {where CONSTRAINER <RE> is returnType of #anElement message of receiverType} *)
(* Reduce is similar to inject except that the first element is used as the injected
element for the rest of the collection. It is often handier than inject. For example:
@@ -1228,7 +1228,7 @@
)
lookup: key <Object>
inTable: tbl <Array[Object|A]>
-matchingSlotDo: matching <[:Int:A| X def]>
+matchingSlotDo: matching <[:Int :A| X def]>
emptySlotDo: empty <[:Int | Y def]>
deletedSlotsDo: marked <[:Int]>
mismatchingSlotsDo: mismatch <[:Int]>
@@ -1258,7 +1258,7 @@
] repeat
)
lookup: key <Object>
-matchingSlotDo: matching <[:Integer:A| X def]>
+matchingSlotDo: matching <[:Integer :A| X def]>
emptySlotDo: empty <[:Integer | Y def]>
deletedSlotsDo: marked <[:Integer]>
^<X|Y> = (
@@ -1953,7 +1953,7 @@
l < j ifTrue: [defaultSort: l to: j ].
i < r ifTrue: [defaultSort: i to: r ].
)
-medianOf: a <Int> and: b <Int> and: c <Int> using: compare <[:E:E| Boolean]> ^<Int> = (
+medianOf: a <Int> and: b <Int> and: c <Int> using: compare <[:E :E| Boolean]> ^<Int> = (
| atA <E> atB <E> atC <E> |
@@ -2098,7 +2098,7 @@
messages #new:sortBlock:, #sortBlock: and the Collection utility message #asSortedList: instead of #new:, #new,
and #asSortedList, respectively. *)|
private usesDefaultSortBlock_private <Boolean>
- private sortBlock_private <[:E:E| Boolean]>
+ private sortBlock_private <[:E :E| Boolean]>
|initCapacity: self class defaultCapacity.
sortBlock_private:: SortedList defaultSortBlock.
usesDefaultSortBlock_private:: true) (
@@ -2150,11 +2150,11 @@
ifTrue: [ contents defaultSort: startGap + 1 to: lastIndex ]
ifFalse: [ contents sort: startGap + 1 to: lastIndex using: sortBlock ]
)
-public sortBlock ^<[:E:E| Boolean]> = (
+public sortBlock ^<[:E :E| Boolean]> = (
^sortBlock_private
)
-public sortBlock: sortBy <[:E:E| Boolean]> = (
+public sortBlock: sortBy <[:E :E| Boolean]> = (
sortBlock_private:: sortBy.
usesDefaultSortBlock_private:: false.
isEmpty ifFalse: [ sort. ].
@@ -2166,7 +2166,7 @@
public defaultCapacity ^<Int> = (
^5
)
-public defaultSortBlock ^<[:E:E| Boolean]> = (
+public defaultSortBlock ^<[:E :E| Boolean]> = (
^[ :el1 <E> :el2 <E> |
(* The default sort block for SortedLists is is not typesafe, but is included for
Smalltalk compatibility (that's the way Smalltalk is!). *)
diff -r 38a47c705f1a CombinatorialParsing.ns
--- a/CombinatorialParsing.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/CombinatorialParsing.ns Fri Jul 28 16:48:38 2017 +0200
@@ -259,7 +259,7 @@
[termBlock value: input] whileFalse: [
- input nextIfAbsent: [blk value:'Premature end of input' value: input position-1]
+ input nextIfAbsent: [blk value:'Premature end of input' value: input position - 1]
].
)
) : (
diff -r 38a47c705f1a KernelForDart.ns
--- a/KernelForDart.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/KernelForDart.ns Fri Jul 28 16:48:38 2017 +0200
@@ -730,7 +730,7 @@
^self asciiValue <= max asciiValue and: [ self >= min asciiValue ]
)
copyFrom: start to: end = (
- ^dart on: self invoke: (dart ident: 'substring') with: {start -1. end}
+ ^dart on: self invoke: (dart ident: 'substring') with: {start - 1. end}
)
copyWithSize: newSize = (
diff -r 38a47c705f1a KernelForSqueak.ns
--- a/KernelForSqueak.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/KernelForSqueak.ns Fri Jul 28 16:48:38 2017 +0200
@@ -793,7 +793,7 @@
All of my members except methods to invoke mixin application should be hidden, and be only accessible by mirrors. *)|
public name <Symbol>
public methodDictionary <MethodDictionary> (* must be slot 2; known to VM *)
-public slots <List[{Symbol.Boolean.Symbol}]> (* name, mutable?, accessModifier *)
+public slots <List[{Symbol. Boolean. Symbol}]> (* name, mutable?, accessModifier *)
public enclosingMixin <InstanceMixin | nil> (* must be slot 4; known to VM *)
public nestedMixins <Map[Symbol, InstanceMixin]> = Map new. (* must be called nestedMixins; known to compiler *)
public applications <WeakSet> = WeakSet new.
diff -r 38a47c705f1a KernelForV8.ns
--- a/KernelForV8.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/KernelForV8.ns Fri Jul 28 16:48:38 2017 +0200
@@ -21,7 +21,7 @@
^js call: (js propertyOf: self at: (js literal: 'slice')) with: {js literal: 1}.
)
public allButLast ^ <MutableList[E]> = (
- ^js call: (js propertyOf: self at: (js literal: 'slice')) with: {js literal: 0. size -1}.
+ ^js call: (js propertyOf: self at: (js literal: 'slice')) with: {js literal: 0. size - 1}.
)
public asArray = (
^self
diff -r 38a47c705f1a MiscBrowsing.ns
--- a/MiscBrowsing.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/MiscBrowsing.ns Fri Jul 28 16:48:38 2017 +0200
@@ -1306,7 +1306,7 @@
)
) : (
)
-public class PackageWithClassesSubject onModel:m = PackageSubject onModel:m (
+public class PackageWithClassesSubject onModel: m = PackageSubject onModel: m (
(* Extends the perspective of a package to be a collection of category subjects (and therefore classes of those categories) rather than just category names. Reports the categories it contains as #categorySubjects, where each category subject is a ClassCategorySubject. *)| |) (
public categorySubjects = (
@@ -1333,7 +1333,7 @@
)
) : (
)
-class PasteboardItemPresenter onSubject:s = Presenter onSubject:s (
+class PasteboardItemPresenter onSubject: s = Presenter onSubject: s (
(* *)| |) (
backgroundColor = (
^Gradient
@@ -1376,7 +1376,7 @@
)
) : (
)
-class PasteboardItemSubject onModel:m = Subject onModel:m (
+class PasteboardItemSubject onModel: m = Subject onModel: m (
(* *)| |) (
public createPresenter = (
@@ -1469,7 +1469,7 @@
)
) : (
)
-class PasteboardSubject onModel:m = Subject onModel:m (
+class PasteboardSubject onModel: m = Subject onModel: m (
(* *)| |model:: List new) (
public = anotherSubject = (
^self class = anotherSubject class
@@ -1546,7 +1546,7 @@
^self onModel: nil
)
)
-class SearchResultsPresenter onSubject:s = ProgrammingPresenter onSubject:s (
+class SearchResultsPresenter onSubject: s = ProgrammingPresenter onSubject: s (
(* *)| |) (
classSearchResults = (
^
@@ -1872,7 +1872,7 @@
^self onModel: nil
)
)
-class UndeclaredReferencesPresenter onSubject:s = AssortedMethodsPresenter onSubject:s (
+class UndeclaredReferencesPresenter onSubject: s = AssortedMethodsPresenter onSubject: s (
(* This presenter is simply a reimplementation of its superclass to ask its subject the subjects to create presenters for. *)| |) (
methodsGroupedByPackage = (
@@ -1890,7 +1890,7 @@
)
) : (
)
-class UndeclaredReferencesSubject onModel:m = Subject onModel:m (
+class UndeclaredReferencesSubject onModel: m = Subject onModel: m (
(* This subject provides the prespective on the references of Undeclared throughout the system. Those methods in the system that are using Undeclared can be found by:
SystemScope theModule allUsersOfUndeclared
diff -r 38a47c705f1a Namespacing.ns
--- a/Namespacing.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/Namespacing.ns Fri Jul 28 16:48:38 2017 +0200
@@ -267,11 +267,11 @@
public respondToSystemChange = (
allLiteralReferences_slot: nil
)
-public smalltalkImplementorsOf: selector <String> do: action <[:Class:Symbol]> = (
+public smalltalkImplementorsOf: selector <String> do: action <[:Class :Symbol]> = (
allSmalltalkBehaviorsDo:
[ :cls | (cls includesSelector: selector) ifTrue: [ action value: cls value: selector ]]
)
-public smalltalkSendersOf: literalIn <String | Symbol | Association> do: action <[:Class:Symbol]> = (
+public smalltalkSendersOf: literalIn <String | Symbol | Association> do: action <[:Class :Symbol]> = (
(* Derived from SystemNavigation class>>allCallsOn: *)
| thorough special literal byte |
thorough:: literalIn isSymbol or: [ literalIn isString ].
diff -r 38a47c705f1a Newspeak2DartCompilation.ns
--- a/Newspeak2DartCompilation.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/Newspeak2DartCompilation.ns Fri Jul 28 16:48:38 2017 +0200
@@ -791,7 +791,7 @@
at: aMsg sel
ifAbsent: [Error signal: 'No outer class named ', aMsg sel].
(* assert:[selectorBinding data isClassDeclarationAST]. *)
- depth: currentDepth - selectorBinding depth -1.
+ depth: currentDepth - selectorBinding depth - 1.
^(ExplicitRecvrAST send: aMsg sel depth: depth)
start: aMsg start;
end: aMsg end
@@ -2229,7 +2229,7 @@
savedPos:: input position.
len: (node end - node start) + 1.
s:: MutableString new: len.
- input position: node start -1.
+ input position: node start - 1.
1 to: len do:
[:index |
s at: index put: input next].
diff -r 38a47c705f1a NewspeakColorization.ns
--- a/NewspeakColorization.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/NewspeakColorization.ns Fri Jul 28 16:48:38 2017 +0200
@@ -169,7 +169,7 @@
)
checkBlockParameter: sd <Token> = (
(coloredText string runeAt: sd start - 1) = 58 ifTrue: [^self].
- self noteRange: #whitespaceWarning from: sd start - 1 to: sd start -1
+ self noteRange: #whitespaceWarning from: sd start - 1 to: sd start - 1
)
checkKeyword: kwd <Token> = (
kwd end >= inputSize ifTrue: [^self].
diff -r 38a47c705f1a NewspeakColorization2.ns
--- a/NewspeakColorization2.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/NewspeakColorization2.ns Fri Jul 28 16:48:38 2017 +0200
@@ -345,7 +345,7 @@
)
checkBlockParameter: sd <Token> = (
(inputString runeAt: sd start - 1) = 58 ifTrue: [^self].
- self noteRange: #whitespaceWarning from: sd start - 1 to: sd start -1
+ self noteRange: #whitespaceWarning from: sd start - 1 to: sd start - 1
)
checkKeyword: kwd <Token> = (
kwd end >= inputSize ifTrue: [^self].
diff -r 38a47c705f1a NewspeakParsing.ns
--- a/NewspeakParsing.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/NewspeakParsing.ns Fri Jul 28 16:48:38 2017 +0200
@@ -127,7 +127,7 @@
^super binaryMsgPattern
wrapper:[:sel :p |
| params |
- params:: List new add:p; yourself.
+ params:: List new add: p; yourself.
MessagePatternAST new selector: sel value parameters: params ;
start: sel start; right: p
].
@@ -481,7 +481,7 @@
public defaultSuperclassAndBody ^ <{List[SendAST]. ClassBodyAST}> = (
^super defaultSuperclassAndBody wrap:
[:body <ClassBodyAST> |
- {{defaultSuperCallAt: body start -1 ending: body start - 1}. body}]
+ {{defaultSuperCallAt: body start - 1 ending: body start - 1}. body}]
)
public doItExpression = (
(* throw out end-of-input indicator *)
@@ -758,7 +758,7 @@
^super nonEmptyBlockTypeArgList wrapper:
[:tas :rt |
| targs |
- targs:: List new addAll:tas; yourself.
+ targs:: List new addAll: tas; yourself.
nil = rt
ifTrue: [targs addLast: (TypeIdAST new name: #Object)]
ifFalse: [targs add: rt last].
@@ -928,8 +928,8 @@
^super statementSequence
wrapper:[:e :rst |
rst isNil
- ifTrue:[List new add:e; yourself]
- ifFalse:[List new add:e; addAll: rst; yourself]
+ ifTrue:[List new add: e; yourself]
+ ifFalse:[List new add: e; addAll: rst; yourself]
].
)
public string = (
diff -r 38a47c705f1a SmalltalkBrowsing.ns
--- a/SmalltalkBrowsing.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/SmalltalkBrowsing.ns Fri Jul 28 16:48:38 2017 +0200
@@ -39,7 +39,7 @@
private ClassCommentPresenter = ide tools ClassCommentPresenter.
private ClassSubject = ide browsing ClassSubject.
||) (
-class ClassListPresenter onSubject: s = ProgrammingPresenter onSubject:s (
+class ClassListPresenter onSubject: s = ProgrammingPresenter onSubject: s (
(* ClassListPresenter displays a list of classes such as subclasses or superclasses of a class provided by its subject, a ClassListSubject. Depending on the size of the list, it may choose to display only a part of the list with a control to expand the display. The list is updated every time the presenter is refreshed. *)|
public title
contentHolder
@@ -82,7 +82,7 @@
)
) : (
)
-class ClassListSubject onModel:m = Subject onModel:m (
+class ClassListSubject onModel: m = Subject onModel: m (
(* ClassListSubject retrieves a list of classes we want displayed together using a ClassListPresenter, such as subclasses or superclasses of a class. *)| public retrievalBlock |) (
public createPresenter = (
@@ -94,7 +94,7 @@
)
) : (
)
-class GlobalReferencesPresenter onSubject:s = AssortedMethodsPresenter onSubject:s (
+class GlobalReferencesPresenter onSubject: s = AssortedMethodsPresenter onSubject: s (
(* The subject is a GlobalReferencesSubject, essentially a collection of methods referencing a global. This presenter displays it as a column of expandable methods. *)| |) (
contentPresenters = (
@@ -151,7 +151,7 @@
)
) : (
)
-public class GlobalReferencesSubject onModel:m = Subject onModel:m (
+public class GlobalReferencesSubject onModel: m = Subject onModel: m (
(* Represents a search for all references to a global. The subject is the global name (a Symbol). Provides a collection of method subjects as the result of the message #methodSubjects. *)| referenceList |) (
public createPresenter = (
@@ -176,7 +176,7 @@
)
) : (
)
-class MethodInheritancePresenter onSubject:s = ProgrammingPresenter onSubject:s (
+class MethodInheritancePresenter onSubject: s = ProgrammingPresenter onSubject: s (
(* *)| superImplementors focus subImplementors |) (
collapseAll = (
@@ -290,7 +290,7 @@
)
) : (
)
-class STClassPresenter onSubject:s = ProgrammingPresenter onSubject:s (|
+class STClassPresenter onSubject: s = ProgrammingPresenter onSubject: s (|
classNamePresenter
messagesContainer
descriptionOrSourceSwitcherHolder
@@ -581,7 +581,7 @@
)
) : (
)
-class STClassSlotsPresenter onSubject:s = ProgrammingPresenter onSubject:s (
+class STClassSlotsPresenter onSubject: s = ProgrammingPresenter onSubject: s (
(* The subject is an STClassPresenter, or in fact anything that responds to the #slotNames message by returning a collection of slot names (Strings). Displays the slots as a list of names (for now static), with the caption saying ''Slots''. *)| contentFlow |) (
definition = (
^
@@ -609,7 +609,7 @@
)
) : (
)
-public class STClassSubject onModel:m = ClassSubject onModel:m (
+public class STClassSubject onModel: m = ClassSubject onModel: m (
(* The model is the class object. (Used for Smalltalk and Newspeak1 classes). Represents the perspective of looking at the class and seeing all of its details. *)| instanceMethodsSubjectX classMethodsSubjectX |) (
public accessesToClassVariableNamed: slotName do: action = (
systemScope
@@ -733,13 +733,13 @@
)
public subclassesSubject = (
- ^(ClassListSubject onModel:nil) retrievalBlock:
+ ^(ClassListSubject onModel: nil) retrievalBlock:
[(model subclasses reject: [:ea | ea isMixinApplication]) asSortedCollection:
[:a :b | a name <= b name]]
)
public superclassesSubject = (
- ^(ClassListSubject onModel:nil) retrievalBlock: [model allSuperclasses]
+ ^(ClassListSubject onModel: nil) retrievalBlock: [model allSuperclasses]
)
public title = (
@@ -751,7 +751,7 @@
)
) : (
)
-class STClassVariablePresenter onSubject:s = ProgrammingPresenter onSubject:s (
+class STClassVariablePresenter onSubject: s = ProgrammingPresenter onSubject: s (
(* *)| |) (
definition = (
^
diff -r 38a47c705f1a VCSCore.ns
--- a/VCSCore.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/VCSCore.ns Fri Jul 28 16:48:38 2017 +0200
@@ -607,7 +607,7 @@
| zippedMirrors |
zippedMirrors:: zippedMirrorsWith: version.
^ zippedMirrors collect: [:each |
- Differencer compare: each last to:each first withAncestor: each second]
+ Differencer compare: each last to: each first withAncestor: each second]
)
public diffsFromFirstParent = (
diff -r 38a47c705f1a VCSNewspeakSourceMirrors.ns
--- a/VCSNewspeakSourceMirrors.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/VCSNewspeakSourceMirrors.ns Fri Jul 28 16:48:38 2017 +0200
@@ -299,7 +299,7 @@
]
ifTrue:[
| sccParts <List> = List new. |
- 1 to: iListAndOrBody size -1 do:[:i | sccParts add: (iListAndOrBody at: i)].
+ 1 to: iListAndOrBody size - 1 do:[:i | sccParts add: (iListAndOrBody at: i)].
bodyOrDot:: iListAndOrBody last children at: 2.
].
body:: bodyOrDot. (* should test if bodyOrDot is collection *)
diff -r 38a47c705f1a VCSSmalltalkSourceMirrors.ns
--- a/VCSSmalltalkSourceMirrors.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/VCSSmalltalkSourceMirrors.ns Fri Jul 28 16:48:38 2017 +0200
@@ -841,12 +841,12 @@
c:: input peek.
c isNil
ifTrue:[false] (* let main routine handle end of input *)
- ifFalse:[c = 39 (* ' *)
+ ifFalse:[c = 39 (* '' *)
ifFalse:[false]
ifTrue:[| pos |
pos:: input position.
input next.
- input peek = 39 (* ' *) ifTrue:[false] ifFalse:[input position: pos. true]
+ input peek = 39 (* '' *) ifTrue:[false] ifFalse:[input position: pos. true]
]
]
]
@@ -890,7 +890,7 @@
public category
|) (
public forClass: n super: s instSide: b classSide: cb = (
- self name:n; superclassName: s; instanceSide: b; classSide: cb
+ self name: n; superclassName: s; instanceSide: b; classSide: cb
)
) : (
)
@@ -963,7 +963,7 @@
^super binaryMsgPattern
wrapper:[:sel :p |
| params |
- params:: List new add:p; yourself.
+ params:: List new add: p; yourself.
MessagePatternAST new selector: sel value parameters: params ;
start: sel start; end: p end
].
diff -r 38a47c705f1a Win32Files.ns
--- a/Win32Files.ns Tue Jul 11 19:25:43 2017 -0700
+++ b/Win32Files.ns Fri Jul 28 16:48:38 2017 +0200
@@ -70,7 +70,7 @@
Win32 CreateDirectory boolValue: cnm address value: sec address
].
)
-public createFileName: dname <String> mode: dmode <Alien> sharing: dsharing <Integer> security: dsecurity <Integer> create: dcreate <Integer> attributes: dattributes <Alien> template:dtemplate <Integer> ^ <Win32Handle> = (
+public createFileName: dname <String> mode: dmode <Alien> sharing: dsharing <Integer> security: dsecurity <Integer> create: dcreate <Integer> attributes: dattributes <Alien> template: dtemplate <Integer> ^ <Win32Handle> = (
^Alien autoFreeAfter:[: selfFreeing <[:Alien | Alien]> | | cstr <CString> |
cstr:: selfFreeing value: (Alien newCString: dname).
@@ -134,7 +134,7 @@
]
)
public setFilePointerHandle: handle distanceLow: p distanceHigh: h moveMethod: m ^ <Boolean> = (
- ^Win32 SetFilePointer boolValue:handle value: p value: h value: m
+ ^Win32 SetFilePointer boolValue: handle value: p value: h value: m
)
public writeFileHandle: handle buffer: buffer count: nBytes numberWritten: ioCount overlapped: o ^ <Boolean> = (
^Win32 WriteFile boolValue: handle value: buffer value: nBytes value: ioCount value: o
@@ -537,7 +537,7 @@
[ | next <Str> |
next:: s upTo: "\".
(next includes: ":")
- ifTrue: [ next:: next,'\' ].
+ ifTrue: [ next:: next,'\\' ].
blk value: (FilePattern for: next) ].
)
extensions ^<FilePattern> = (
@@ -585,7 +585,7 @@
^pat pattern last = "\"
ifTrue: [ pat pattern, self pattern ]
- ifFalse: [ pat pattern,'\', self pattern ]
+ ifFalse: [ pat pattern,'\\', self pattern ]
)
terminalPathsDo: blk <[:FilePath]>
= (
@@ -603,8 +603,8 @@
prefix:: ''.
]
ifFalse: [
- allpat:: self containingDirectory pattern, '\*.*'.
- prefix:: (FilePattern forAll: (els copyFrom: 1 to: els size - 1)) pattern,'\'
+ allpat:: self containingDirectory pattern, '\\*.*'.
+ prefix:: (FilePattern forAll: (els copyFrom: 1 to: els size - 1)) pattern,'\\'
].
pat:: els last pattern.
[ hnd:: api findFirstFilePattern: allpat
@@ -648,7 +648,7 @@
^"*"
)
pathSeparatorCharacter ^ <Character> = (
- ^'\'
+ ^'\\'
)
public patternHasWildcards: pat <Str> ^<Boolean> = (
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment