'From Squeak 2.4b of April 23, 1999 on 25 May 1999 at 12:07:21 am'! "Change Set: Dandelion-patch Date: 24 May 1999 Author: Masashi Umezawa PatchNo: 2.0a -added Mac support methods in DlPortableFilePath. Copyright (C) 1999 Masashi Umezawa mail: umejava@mars.dti.ne.jp www: http://www.mars.dti.ne.jp/~umejava/ This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details.(http://www.gnu.org)"! !DlPortableFilePath methodsFor: 'actions' stamp: 'M.U 5/25/1999 00:06'! forceExist "supposing that currentDir already exists" | dir sz comp | dir := self currentDir. (self isInDrivePlatform and: [dir pathName = '']) ifTrue: [dir := FileDirectory on: self drive]. sz := self pathComponents size. 1 to: sz do: [:idx | comp := self pathComponents at: idx. idx == sz ifTrue: [self isDirectoryPath ifTrue: [(dir includesKey: comp asString) ifFalse: [dir createDirectory: comp]] ifFalse: [(dir includesKey: comp asString) ifFalse: [(dir newFileNamed: comp) close]]] ifFalse: [(dir includesKey: comp asString) ifFalse: [dir createDirectory: comp]. dir := dir directoryNamed: comp]].! ! !DlPortableFilePath methodsFor: 'actions' stamp: 'M.U 5/24/1999 23:35'! forceRemove "Squeak misteriously does not provide directory-removing... So this implementation is incomplete" "You should also aware that the execution is somethimes dangerous.. (if I am in root dir..)" | dir lastIndex comps | dir := self currentDir. (self isInDrivePlatform and: [dir pathName = '']) ifTrue: [dir := FileDirectory on: self drive]. comps := self pathComponents. lastIndex := self isDirectoryPath ifTrue: [comps size] ifFalse: [comps size - 1]. 1 to: lastIndex do: [:idx | dir := dir directoryNamed: (comps at: idx)]. self isDirectoryPath ifTrue: [self privRemoveAllFilesIn: dir.] ifFalse: [dir deleteFileNamed: (comps last) ifAbsent:[]]. ! ! !DlPortableFilePath methodsFor: 'actions' stamp: 'M.U 5/25/1999 00:06'! isExisting | dir sz comp | self isDirectoryPath not ifTrue: [^ FileStream isAFileNamed: self pathName]. dir := self currentDir. (self isInDrivePlatform and: [dir pathName = '']) ifTrue: [dir := FileDirectory on: self drive]. sz := self pathComponents size. 1 to: sz do: [:idx | comp := self pathComponents at: idx. (dir includesKey: comp) ifFalse: [^ false]. dir := dir directoryNamed: comp]. ^ true! ! !DlPortableFilePath methodsFor: 'actions' stamp: 'M.U 5/24/1999 23:36'! pathName | str | str := WriteStream with: self currentDir pathName. (self isAbsolute and: [self isInDrivePlatform]) ifTrue: [str nextPutAll: self drive]. self pathComponents do: [:each | str nextPut: self pathSeparator. str nextPutAll: each]. ^ str contents! ! !DlPortableFilePath methodsFor: 'testing' stamp: 'M.U 5/24/1999 23:35'! isInDrivePlatform ^ self isInDos or: [self isInMac].! ! !DlPortableFilePath methodsFor: 'testing' stamp: 'M.U 5/24/1999 23:34'! isInMac ^ FileDirectory default class == MacFileDirectory! !