[squeak-dev] The Trunk: Network-pre.228.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 11 15:08:01 UTC 2018


Patrick Rein uploaded a new version of Network to project The Trunk:
http://source.squeak.org/trunk/Network-pre.228.mcz

==================== Summary ====================

Name: Network-pre.228
Author: pre
Time: 11 December 2018, 4:07:36.560299 pm
UUID: 1dd9f0d5-8662-4b3d-b6ba-28ac11852dd3
Ancestors: Network-pre.227

Recategorizes methods in the Network package and applies a typo fix and an indentation fix.

=============== Diff against Network-pre.227 ===============

Item was changed:
+ ----- Method: Authorizer class>>unauthorizedFor: (in category 'utilities') -----
- ----- Method: Authorizer class>>unauthorizedFor: (in category 'as yet unclassified') -----
  unauthorizedFor: realm
  	^'HTTP/1.0 401 Unauthorized', self crlf, 'WWW-Authenticate: Basic realm="Squeak/',realm,'"',
  	String crlfcrlf, '<html><title>Unauthorized</title><body><h2>Unauthorized for ',realm, '</h2></body></html>'
  
  !

Item was changed:
+ ----- Method: HttpUrl class>>shutDown (in category 'system startup') -----
- ----- Method: HttpUrl class>>shutDown (in category 'as yet unclassified') -----
  shutDown
  	"Forget all cached passwords, so they won't stay in the image"
  
  	Passwords := nil.!

Item was changed:
  Object subclass: #MIMEDocument
  	instanceVariableNames: 'mainType subType content fields url parts'
  	classVariableNames: 'MIMEdatabase'
  	poolDictionaries: ''
  	category: 'Network-Url'!
  
+ !MIMEDocument commentStamp: 'pre 7/6/2017 13:58' prior: 0!
+ a MIME object, along with its type and the URL it was found at (if any)
+ 
+ Design decisions:
+ - The API for using the content of the MIME object inside Squeak returns Strings 
+ in Squeak encoding. The serializing methods return the content serialized according 
+ to the content-type and content-transfer-encoding --pre!
- !MIMEDocument commentStamp: '<historical>' prior: 0!
- a MIME object, along with its type and the URL it was found at (if any)!

Item was changed:
  Object subclass: #Password
  	instanceVariableNames: 'cache sequence'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Network-Kernel'!
  
+ !Password commentStamp: 'pre 12/11/2018 15:53' prior: 0!
- !Password commentStamp: '<historical>' prior: 0!
  "Hold a password.  There are three ways to get the password.
  
  If there is no password (sequence == nil), ask the user for it.
  
+ If the user supplied one during this session, return that.  It is cleared at shutDown.
- If the use supplied one during this session, return that.  It is cleared at shutDown.
  
  If sequence is a number, get the server passwords off the disk.  File 'sqk.info' must be in the same folder 'Squeak.sources' file.  Decode the file.  Return the password indexed by sequence."!

Item was changed:
+ ----- Method: Password class>>shutDown (in category 'system startup') -----
- ----- Method: Password class>>shutDown (in category 'as yet unclassified') -----
  shutDown
  	"Forget all cached passwords, so they won't stay in the image"
  
  	self allSubInstancesDo: [:each | each cache: nil].!

Item was changed:
+ ----- Method: Password>>decode: (in category 'private') -----
- ----- Method: Password>>decode: (in category 'as yet unclassified') -----
  decode: string
  	"Xor with secret number -- just so file won't have raw password in it"
  	| kk rand |
  	rand := Random new seed: 234237.
  	kk := (ByteArray new: string size) collect: [:bb | (rand next * 255) asInteger].
  	1 to: kk size do: [:ii |
  		kk at: ii put: ((kk at: ii) bitXor: (string at: ii) asciiValue)].
  	^ kk asString!

Item was changed:
+ ----- Method: Password>>serverPasswords (in category 'accessing') -----
- ----- Method: Password>>serverPasswords (in category 'as yet unclassified') -----
  serverPasswords
  	"Get the server passwords off the disk and decode them. The file 'sqk.info' must be in some folder that Squeak thinks is special (vm folder, or default directory).  (Note: This code works even if you are running with no system sources file.)"
  
  	| sfile |
  	(sfile := FileDirectory lookInUsualPlaces: 'sqk.info') ifNil: [^ nil].
  		"If not there, Caller will ask user for password"
  		"If you don't have this file, and you really do want to release an update, 
  		 contact Ted Kaehler."
  	^ (self decode: (sfile contentsOfEntireFile)) lines
  !

Item was changed:
+ ----- Method: RemoteFileStream>>close (in category 'file status') -----
- ----- Method: RemoteFileStream>>close (in category 'as yet unclassified') -----
  close
  	"Write if we have data to write.  FTP files are always binary to preserve the data exactly.  The binary/text (ascii) flag is just for tell how the bits are delivered from a read."
  
  	remoteFile writable ifTrue: [
  			remoteFile putFile: (self as: RWBinaryOrTextStream) reset named: remoteFile fileName]!

Item was changed:
+ ----- Method: RemoteFileStream>>contentsOfEntireFile (in category 'accessing') -----
- ----- Method: RemoteFileStream>>contentsOfEntireFile (in category 'as yet unclassified') -----
  contentsOfEntireFile
  	"Fetch the data off the server and store it in me.  But not if I already have it."
  
  	readLimit := readLimit max: position.
  	localDataValid ifTrue: [^ super contentsOfEntireFile].
  	collection size = 0 ifTrue: [self on: (String new: 2000)].
  	remoteFile getFileNamed: remoteFile fileName into: self.	"sets localDataValid := true"
  	^ super contentsOfEntireFile!

Item was changed:
+ ----- Method: RemoteFileStream>>dataIsValid (in category 'accessing') -----
- ----- Method: RemoteFileStream>>dataIsValid (in category 'as yet unclassified') -----
  dataIsValid
  
  	localDataValid := true.!

Item was changed:
+ ----- Method: RemoteFileStream>>directory (in category 'accessing') -----
- ----- Method: RemoteFileStream>>directory (in category 'as yet unclassified') -----
  directory
  	^ remoteFile!

Item was changed:
+ ----- Method: RemoteFileStream>>directoryUrl (in category 'accessing') -----
- ----- Method: RemoteFileStream>>directoryUrl (in category 'as yet unclassified') -----
  directoryUrl
  	^ remoteFile directoryUrl!

Item was changed:
+ ----- Method: RemoteFileStream>>localName (in category 'accessing') -----
- ----- Method: RemoteFileStream>>localName (in category 'as yet unclassified') -----
  localName
  	^ remoteFile fileName!

Item was changed:
+ ----- Method: RemoteFileStream>>openReadOnly (in category 'accessing') -----
- ----- Method: RemoteFileStream>>openReadOnly (in category 'as yet unclassified') -----
  openReadOnly
  	"If we have data, don't reread."
  
  	self readOnly.
  	readLimit := readLimit max: position.
  	localDataValid ifFalse: [remoteFile getFileNamed: remoteFile fileName into: self].
  		"sets localDataValid := true"!

Item was changed:
+ ----- Method: RemoteFileStream>>readOnly (in category 'accessing') -----
- ----- Method: RemoteFileStream>>readOnly (in category 'as yet unclassified') -----
  readOnly
  	^ remoteFile readOnly!

Item was changed:
+ ----- Method: RemoteFileStream>>remoteFile (in category 'accessing') -----
- ----- Method: RemoteFileStream>>remoteFile (in category 'as yet unclassified') -----
  remoteFile
  	^ remoteFile!

Item was changed:
+ ----- Method: RemoteFileStream>>remoteFile: (in category 'accessing') -----
- ----- Method: RemoteFileStream>>remoteFile: (in category 'as yet unclassified') -----
  remoteFile: aServerFile
  	remoteFile := aServerFile.
  	localDataValid := false.	"need to read from the server"!

Item was changed:
+ ----- Method: RemoteFileStream>>sleep (in category 'file directory') -----
- ----- Method: RemoteFileStream>>sleep (in category 'as yet unclassified') -----
  sleep
  	"If we are done, then let the server know"
  
  	self close.
  	remoteFile sleep.!

Item was changed:
+ ----- Method: ServerFile>>asStream (in category 'converting') -----
- ----- Method: ServerFile>>asStream (in category 'as yet unclassified') -----
  asStream
  	"Return a RemoteFileStream (subclass of RWBinaryOrTextStream) on the contents of the remote file I represent.  For reading only.  This method is probably misnamed.  Maybe call it makeStream"
  
  	^ self readOnlyFileNamed: self fileName!

Item was changed:
+ ----- Method: ServerFile>>directoryUrl (in category 'accessing') -----
- ----- Method: ServerFile>>directoryUrl (in category 'as yet unclassified') -----
  directoryUrl
  	| ru |
  	"A url to the directory this file is in"
  
  	ru := self realUrl.
  	^ ru copyFrom: 1 to: (ru size - fileName size)!

Item was changed:
+ ----- Method: ServerFile>>exists (in category 'file directory') -----
- ----- Method: ServerFile>>exists (in category 'as yet unclassified') -----
  exists
  	"Return true if the file exists on the server already"
  
  	^ self fileExists: fileName!

Item was changed:
+ ----- Method: ServerFile>>fileName (in category 'accessing') -----
- ----- Method: ServerFile>>fileName (in category 'as yet unclassified') -----
  fileName
  	"should this be local or as in a url?"
  
  	urlObject ifNotNil: [^ urlObject path last].	"path last encodeForHTTP ?"
  	^ fileName!

Item was changed:
+ ----- Method: ServerFile>>fileName: (in category 'accessing') -----
- ----- Method: ServerFile>>fileName: (in category 'as yet unclassified') -----
  fileName: aString
  
+ 	urlObject ~~ nil  "type == #file" 
+ 		ifTrue: [urlObject path at: urlObject path size put: aString]
+ 		ifFalse: [fileName := aString]!
- urlObject ~~ nil  "type == #file" 
- 	ifTrue: [urlObject path at: urlObject path size put: aString]
- 	ifFalse: [fileName := aString]!

Item was changed:
+ ----- Method: ServerFile>>fileNameRelativeTo: (in category 'accessing') -----
- ----- Method: ServerFile>>fileNameRelativeTo: (in category 'as yet unclassified') -----
  fileNameRelativeTo: aServerDir
  	"Produce an absolute fileName from me and an absolute directory"
  	urlObject isAbsolute ifFalse: [
  		(aServerDir urlObject ~~ nil and: [aServerDir urlObject isAbsolute]) 
  			ifTrue: [urlObject 
  				privateInitializeFromText: urlObject pathString 
  				relativeTo: aServerDir urlObject]
  			ifFalse: [urlObject default]].	"relative to Squeak directory"
  	^ urlObject pathForDirectory, self fileName!

Item was changed:
+ ----- Method: ServerFile>>fullPath: (in category 'accessing') -----
- ----- Method: ServerFile>>fullPath: (in category 'as yet unclassified') -----
  fullPath: serverAndDirectory
  	"Parse and save a full path.  Separate out fileName at the end."
  
  	| delim ii |
  	super fullPath: serverAndDirectory.		"set server and directory"
  	self isTypeFile ifTrue: [
  		fileName :=  ''.
  		^ self
  	].
  	delim := self pathNameDelimiter.
  	ii := directory findLast: [:c | c = delim].
  	ii = 0
  		ifTrue: [self error: 'expecting directory and fileName']
  		ifFalse: [fileName := directory copyFrom: ii+1 to: directory size.
  			directory := (directory copyFrom: 1 to: directory size - fileName size - 1)].!

Item was changed:
+ ----- Method: ServerFile>>localName (in category 'file directory') -----
- ----- Method: ServerFile>>localName (in category 'as yet unclassified') -----
  localName
  
  	^ self fileName!

Item was changed:
+ ----- Method: ServerFile>>readOnly (in category 'file modes') -----
- ----- Method: ServerFile>>readOnly (in category 'as yet unclassified') -----
  readOnly
  	"Set the receiver to be read-only"
  
  	rwmode := false!

Item was changed:
+ ----- Method: ServerFile>>readWrite (in category 'file modes') -----
- ----- Method: ServerFile>>readWrite (in category 'as yet unclassified') -----
  readWrite
  	"Set the receiver to be writable"
  
  	rwmode := true!

Item was changed:
+ ----- Method: ServerFile>>realUrl (in category 'accessing') -----
- ----- Method: ServerFile>>realUrl (in category 'as yet unclassified') -----
  realUrl
  	"a fully expanded version of the url we represent.  Prefix the path with http: or ftp: or file:"
  
  	self isTypeFile ifTrue: [
  		self fileNameRelativeTo: self.
  		^ urlObject asString
  	].
  	^ self typeWithDefault asString, '://', self pathName, '/', fileName	"note difference!!"
  	!

Item was changed:
+ ----- Method: ServerFile>>writable (in category 'file modes') -----
- ----- Method: ServerFile>>writable (in category 'as yet unclassified') -----
  writable
  	^ rwmode!

Item was changed:
+ ----- Method: SuperSwikiServer class>>currentSuperSwiki (in category 'instances') -----
- ----- Method: SuperSwikiServer class>>currentSuperSwiki (in category 'as yet unclassified') -----
  currentSuperSwiki
  
  	"make this return nil to disable SuperSwiki hack"
  
  	^self defaultSuperSwiki
  
  !

Item was changed:
+ ----- Method: SuperSwikiServer class>>defaultEncodingName (in category 'defaults') -----
- ----- Method: SuperSwikiServer class>>defaultEncodingName (in category 'as yet unclassified') -----
  defaultEncodingName
  	Locale current isoLanguage = 'ja' ifTrue: [^'shift_jis' copy] ifFalse: [^'latin1' copy].
  !

Item was changed:
+ ----- Method: SuperSwikiServer class>>defaultSuperSwiki (in category 'instances') -----
- ----- Method: SuperSwikiServer class>>defaultSuperSwiki (in category 'as yet unclassified') -----
  defaultSuperSwiki
  
  	^SuperSwikiServer new 
  		type: #http;
  		server: self defaultSuperSwikiIPAddress;
  		directory: '/super/SuperSwikiProj'
  	
  !

Item was changed:
+ ----- Method: SuperSwikiServer class>>defaultSuperSwikiIPAddress (in category 'instances') -----
- ----- Method: SuperSwikiServer class>>defaultSuperSwikiIPAddress (in category 'as yet unclassified') -----
  defaultSuperSwikiIPAddress
  
  	^'209.143.91.36'
  !

Item was changed:
+ ----- Method: SuperSwikiServer class>>testOnlySuperSwiki (in category 'tests') -----
- ----- Method: SuperSwikiServer class>>testOnlySuperSwiki (in category 'as yet unclassified') -----
  testOnlySuperSwiki
  
  	^SuperSwikiServer new 
  		type: #http;
  		server: self defaultSuperSwikiIPAddress;
  		directory: '/super/SuperSwikiProj'
  	
  !

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>directory (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>directory (in category 'as yet unclassified') -----
  directory
  
  	^directory url!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>directory: (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>directory: (in category 'as yet unclassified') -----
  directory: x
  
  	directory := x!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>directoryObject (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>directoryObject (in category 'as yet unclassified') -----
  directoryObject
  
  	^directory!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>directoryUrl (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>directoryUrl (in category 'as yet unclassified') -----
  directoryUrl
  
  	^directory url!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>directoryUrl: (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>directoryUrl: (in category 'as yet unclassified') -----
  directoryUrl: x
  
  	directoryUrl := x!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>fileName (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>fileName (in category 'as yet unclassified') -----
  fileName
  
  	^localName!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>isTypeHTTP (in category 'testing') -----
- ----- Method: SwikiPseudoFileStream>>isTypeHTTP (in category 'as yet unclassified') -----
  isTypeHTTP
  
  	^true!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>localName (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>localName (in category 'as yet unclassified') -----
  localName
  
  	^localName!

Item was changed:
+ ----- Method: SwikiPseudoFileStream>>localName: (in category 'accessing') -----
- ----- Method: SwikiPseudoFileStream>>localName: (in category 'as yet unclassified') -----
  localName: x
  
  	localName := x!



More information about the Squeak-dev mailing list