Skip to content

Commit

Permalink
sort locators to get the most matching path. Thanks to @Jesic for thi…
Browse files Browse the repository at this point in the history
…s enhancement
  • Loading branch information
demarey committed Jun 2, 2020
1 parent 2564418 commit 38bf303
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 8 deletions.
20 changes: 12 additions & 8 deletions src/FileSystem-Core/FileLocator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -248,14 +248,18 @@ FileLocator class >> flushCaches [
FileLocator class >> fromPath: aPath [
"Returns a file locator if aPath is a reference to a supported origin or is a child of an origin.
Else returns nil.
Should not be called direcly. Prefer the use of Path or String>>#asFileLocatorOrReference "
self supportedOrigins
detect: [ :origin | | locator |
locator := self perform: origin.
locator asPath = aPath or: [ locator contains: aPath] ]
ifFound: [ :origin | | locator |
locator := self perform: origin.
^ locator resolve: (aPath relativeToPath: locator asPath) ].
Should not be called direcly. Prefer the use of Path or String>>#asFileLocatorOrReference "

| locators locatorsPaths |
locators := self supportedOrigins
collect: [ :origin | self origin: origin ]
as: OrderedCollection.
locatorsPaths := (locators collect: [ :e | e -> e asPath ]) asDictionary.
(locators sort:
[ :a :b | ((locatorsPaths at: a) containsPath: (locatorsPaths at: b)) not ])
do: [ :locator |
((locatorsPaths at: locator) = aPath or: [ (locatorsPaths at: locator) containsPath: aPath ])
ifTrue: [ ^ locator resolve: (aPath relativeToPath: (locatorsPaths at: locator)) ] ].
^ nil
]

Expand Down
15 changes: 15 additions & 0 deletions src/FileSystem-Tests-Core/FileLocatorTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,21 @@ FileLocatorTest >> testFromPathReturnsNilIfPathNotPartOfAnOrigin [
equals: nil.
]

{ #category : #'creation tests' }
FileLocatorTest >> testGetRightLocatorWhenCreatingFromString [
| path |
path := (FileLocator documents / 'foo') fullName.

locator := FileLocator fromString: path.

self
assert: locator origin
equals: #documents.
self
assert: locator fullName
equals: path.
]

{ #category : #tests }
FileLocatorTest >> testIfAbsent [
| reference |
Expand Down

0 comments on commit 38bf303

Please sign in to comment.