MCHttpRepository.st
author Claus Gittinger <cg@exept.de>
Sun, 26 Aug 2018 16:45:29 +0200
changeset 1069 5ea6b7f00935
parent 1053 86dccda75716
child 1073 8dc1f701d37e
permissions -rw-r--r--
#FEATURE by cg class: MCHttpRepository comment/format in: #loadAllFileNames #password changed: #allFileNames #asCreationTemplate #assertNonBinaryResponse: #description #displayProgress:during: #displayString #locationWithTrailingSlash #userAndPasswordFromSettingsDo: category of: #asCreationTemplate #userAndPasswordFromSettingsDo: #versionReaderForFileNamed: #versionReaderForFileNamed:do:

"{ Encoding: utf8 }"

"{ Package: 'stx:goodies/monticello' }"

"{ NameSpace: Smalltalk }"

MCFileBasedRepository subclass:#MCHttpRepository
	instanceVariableNames:'location user password readerCache'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Monticello-RemoteRepositories'
!

!MCHttpRepository class methodsFor:'documentation'!

documentation
"
    I am general http repository for monticello.
    I support the general protocol for listing files in a remote repository.
"
! !

!MCHttpRepository class methodsFor:'initialization'!

clearPasswords
	self allSubInstancesDo: [:ea | ea password: ''].
! !

!MCHttpRepository class methodsFor:'instance creation'!

basicFromUrl: aZnUrl
	^ aZnUrl hasUsername
		ifFalse: [ self location: aZnUrl location ]
		ifTrue: [ (self repositoryClassFor: aZnUrl location) new
				location: aZnUrl location;
				user: aZnUrl username;
				password: aZnUrl password;
				yourself  ]
!

location: location
	^ MCServerRegistry uniqueInstance 
		repositoryAt: location credentialsDo: [ :username :password |
			(self repositoryClassFor: location) new
				location: location;
				user: username;
				password: password;
				yourself ]
!

location: location user: user password: password
	^ self new
		location: location;
		user: user;
		password: password
!

pharoInboxRepository
	^ self location: 'http://smalltalkhub.com/mc/Pharo/Pharo60Inbox/main'.
!

pharoRepository
	^ self location: 'http://smalltalkhub.com/mc/Pharo/Pharo60/main'.
!

project: aProjectIdentifier
	^ self location: self baseURL, aProjectIdentifier
!

repositoryClassFor: location
	MCHttpRepository subclassesDo: [ :subclass | 
		(subclass isResponsibleFor: location)
			ifTrue: [ ^ subclass ]].
	^ MCHttpRepository
! !

!MCHttpRepository class methodsFor:'*Komitter-Models'!

pharoLocations
	"Answer the locations for both pharo and pharo inbox repositories.
	No commit should actually be pushed directly there"

	^ #('http://smalltalkhub.com/mc/Pharo/Pharo60/main' 
		'http://smalltalkhub.com/mc/Pharo/Pharo60/main/' 
		'http://smalltalkhub.com/mc/Pharo/Pharo60Inbox/main'
		'http://smalltalkhub.com/mc/Pharo/Pharo60Inbox/main/'
		'http://smalltalkhub.com/mc/Pharo/Pharo50Inbox/main'
		'http://smalltalkhub.com/mc/Pharo/Pharo50Inbox/main/')
! !

!MCHttpRepository class methodsFor:'*MonticelloGUI'!

fillInTheBlankRequest
	^ 'HTTP Repository:'
			
!

morphicConfigure
	^ self fillInTheBlankConfigure
! !

!MCHttpRepository class methodsFor:'accessing'!

baseURL
	^ ''
!

urlSchemes
	^ #(http https)
! !

!MCHttpRepository class methodsFor:'queries'!

creationTemplate
	^self creationTemplateLocation: 'http://www.squeaksource.com/'
		user: 'squeak'
		password: 'squeak'

!

creationTemplateLocation: location user: user password: password
        ^
self name,'
        location: %1
        user: %2
        password: %3' 
            bindWith: location storeString 
            with: user storeString
            with: password storeString

    "Modified: / 16-09-2010 / 14:34:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-08-2018 / 14:28:47 / Claus Gittinger"
!

description
	^ 'HTTP'
! !

!MCHttpRepository class methodsFor:'testing'!

isResponsibleFor: aURLString
	"Override in subclasses to enable custom instances for certain URLs"
	^ true
! !

!MCHttpRepository methodsFor:'*Komitter-Models'!

isPrivatePharoRepository
	
	^ self class pharoLocations includes: self location
!

isRemote
	^ self isPrivatePharoRepository not
!

koRemote

	^ KomitHttpRemote new
		remote: self;
		yourself
! !

!MCHttpRepository methodsFor:'*metacello-mc'!

asRepositorySpecFor: aMetacelloMCProject

	^(aMetacelloMCProject repositorySpec)
		description:  self description;
	 	type: 'http';
		yourself
! !

!MCHttpRepository methodsFor:'accessing'!

credentials
	^ MCServerCredentials user: self user password: self password
!

credentials: mcServerCredentials
	self user: mcServerCredentials username.
	self password: mcServerCredentials password.
!

location
      ^location 
!

location: aUrlString
	location := aUrlString
!

locationWithTrailingSlash
        ^ (self location endsWith: '/')
                ifTrue: [self location]
                ifFalse: [self location, '/']

    "Modified: / 26-08-2018 / 16:16:22 / Claus Gittinger"
!

password
        self userAndPasswordFromSettingsDo: [:usr :pwd | ^pwd].

        self user isEmpty ifTrue: [^password ? ''].

        [password isEmpty] whileTrue: [
                | answer dialog |

                dialog := UIManager isNil ifTrue:[Dialog] ifFalse:[ UIManager default ].

                "Give the user a chance to change the login"
                answer := dialog request: 'User name for ' translated, String cr, self location
                        initialAnswer: self user.
                answer isEmpty
                        ifTrue: [^password]
                        ifFalse: [self user: answer].
                
                password := UIManager default requestPassword: 'Password for' translated, ' "', self user, '" ', 'at ' translated, String cr, self location.
        ].

        ^ password

    "Modified: / 26-08-2018 / 16:16:29 / Claus Gittinger"
!

password: passwordString
	password := passwordString
!

project
	"Return a project name"
	^ (self location splitOn: $/) last
!

user
	self userAndPasswordFromSettingsDo: [:usr :pwd | ^usr].
	"not in settings"
	^user
!

user: userString
	user := userString
! !

!MCHttpRepository methodsFor:'actions'!

parseFileNamesFromStream: aStream
	| names fullName |
	names := OrderedCollection new.
	[aStream atEnd] whileFalse:
		[[aStream upTo: $<. {$a. $A. nil} includes: aStream next] whileFalse.
		aStream upTo: $".
		aStream atEnd ifFalse: [
			fullName := aStream upTo: $".
			names add: fullName urlDecoded ]].
	^ names
!

retryOnCredentialRequest: aBlock
	aBlock	on: MCPermissionDenied do: [ :error | |credentials| 
		credentials := MCCredentialsRequest 
							signalUrl: self location
							username: self user
							password: self password.
		credentials 
			ifNotNil: [ 
				self credentials: credentials.
				^ self retryOnCredentialRequest: aBlock ]]
!

urlForFileNamed: aString
	^ self locationWithTrailingSlash, aString urlEncoded
! !

!MCHttpRepository methodsFor:'displaying'!

displayString

    ^ self location

    "Created: / 14-09-2010 / 23:20:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-08-2018 / 16:15:38 / Claus Gittinger"
! !

!MCHttpRepository methodsFor:'i/o'!

cacheRawVersionNamed: aString stream: contents
	"directly forward the contents to the cache repository. 
	this avoids and unnecessary serialization step"
	MCCacheRepository uniqueInstance 
		writeStreamForFileNamed: aString 
		replace: true 
		do: [ :s| s nextPutAll: contents ]
!

displayProgress: label during: workBlock
        | nextUpdateTime |

        Smalltalk isSmalltalkX ifTrue:[
            workBlock value.
        ].
        
        nextUpdateTime := 0.
        ^UIManager default displayProgress: label 
                from: 0.0 to: 1.0 during:[:bar|
                        [workBlock value] on: HTTPProgress do:[:ex|
                                (ex total == nil or: [ex amount == nil]) ifFalse:[
                                        (nextUpdateTime < Time millisecondClockValue 
                                                or:[ex total = ex amount]) ifTrue:[
                                                        bar current: ex amount asFloat / ex total asFloat.
                                                        nextUpdateTime := Time millisecondClockValue + 100.
                                        ].
                                ].
                                ex resume.
                        ]
                ].

    "Modified: / 26-08-2018 / 14:57:19 / Claus Gittinger"
!

handleUnsuccessfulResponse: aZnResponse
	(#(403 401) includes: aZnResponse code)
		ifTrue: [ MCPermissionDenied signalFor: self ].
	Error signal: 'Could not save version.'
!

loadAllFileNames
        | client response |
        self displayProgress: 'Loading all file names from ', self description during: [
            Smalltalk isSmalltalkX ifTrue:[
                response := HTTPInterface 
                                get: self locationWithTrailingSlash, '?C=M;O=D' 
                                userName: self user 
                                password: self password.
                response responseCode ~= 200 ifTrue: [
                    self error:('Could not access "',self location,'" (',response response asString,')')
                ].
            ] ifFalse:[    
                client := self httpClient.
                client
                        ifFail: [ :exception | 
                                (exception className beginsWith: 'Zn')
                                        ifTrue: [ MCRepositoryError signal: 'Could not access ', self location, ': ', exception printString ]
                                        ifFalse: [ exception pass ] ];
                        url: self locationWithTrailingSlash;
                        queryAt: 'C' put: 'M;O=D';      "legacy that some servers maybe expect"
                        get.
                self assertNonBinaryResponse: client response 
            ].
        ].
        ^ self parseFileNamesFromStream: client contents readStream

    "Modified: / 26-08-2018 / 16:16:11 / Claus Gittinger"
! !

!MCHttpRepository methodsFor:'private'!

asCreationTemplate
        ^self class creationTemplateLocation: self location user: user password: password

    "Modified: / 26-08-2018 / 16:15:28 / Claus Gittinger"
!

assertBinaryResponse: response 

	response contentType isBinary ifFalse: [ 
		MCRepositoryError signal: 'Expected a binary response instead of ', response contentType printString ].
!

assertNonBinaryResponse: response 
    Smalltalk isSmalltalkX ifTrue:[
        response contentType = 'text/plain' ifFalse:[
            Error "MCRepositoryError" signal: 'Did not expect a binary response but got ', response contentType printString 
        ]. 
        ^ self.
    ].    
    response contentType isBinary ifTrue: [ 
        MCRepositoryError signal: 'Did not expect a binary response but got ', response contentType printString 
    ].

    "Modified: / 26-08-2018 / 15:02:39 / Claus Gittinger"
!

entityStreamContents: aBlock
	"Generate output in a buffer because we need the length"
	
	| stream |
	stream := RWBinaryOrTextStream on: String new.
	aBlock value: stream.
	stream reset.
	^ (ZnStreamingEntity type: ZnMimeType applicationOctetStream)
		stream: stream;
		contentLength: stream size;
		yourself
!

httpClient
	"Return a new, specifically configured instance of the HTTP client for internal use.
	Note how we request GZIP compression and will signal progress."

	^ ZnClient new
		systemPolicy;
		beOneShot;
		username: self user password: self password;
	
		signalProgress: true;
		yourself
!

userAndPasswordFromSettingsDo: aBlock
        "The mcSettings file in ExternalSettings preferenceDirectory should contain entries for each account:
        
                account1: *myhost.mydomain* user:password
                account2: *otherhost.mydomain/somerep* dXNlcjpwYXNzd29yZA==

        That is it must start with 'account', followed by anything to distinguish accounts, and a colon. Then comes a match expression for the repository url, and after a space the user:password string.
        
        To not have the clear text password on your disc, you can base64 encode it:
                        (Base64MimeConverter mimeEncode: 'user:password' readStream) contents
        "

        | entry userAndPassword |
        Settings ifNotNil: [
                Settings keysAndValuesDo: [:key :value |
                        (key asLowercase beginsWith: 'account') ifTrue: [
                                entry := value findTokens: '     '.
                                (entry first match: self location) ifTrue: [
                                        userAndPassword := entry second.
                                        (userAndPassword includes: $:) ifFalse: [
                                                userAndPassword := (Base64MimeConverter mimeDecodeToChars: userAndPassword readStream) contents].
                                        userAndPassword := userAndPassword findTokens: $:.
                                        ^aBlock value: userAndPassword first 
                                                value: userAndPassword second 
                                        ]
                        ]
                ]
        ].
        ^nil

    "Modified: / 26-08-2018 / 16:16:02 / Claus Gittinger"
!

versionReaderForFileNamed: aString
	readerCache ifNil: [readerCache := Dictionary new].
	^ readerCache at: aString ifAbsent:
		[self resizeCache: readerCache.
		super versionReaderForFileNamed: aString do:
			[:r |
			r ifNotNil: [readerCache at: aString put: r]]]
	
!

versionReaderForFileNamed: aString do: aBlock

    | r |

    ^(r := self versionReaderForFileNamed: aString) ifNotNil: [aBlock value: r]

    "Modified: / 14-09-2010 / 19:39:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MCHttpRepository methodsFor:'required'!

allFileNames
        | response |
        response := HTTPInterface 
                        get: self locationWithTrailingSlash, '?C=M;O=D' 
                        userName: self user 
                        password: self password.
        response responseCode ~= 200 
            ifTrue: [self error:('Could not access "',self location,'" (',response response asString,')')].
        ^ self parseFileNamesFromStream: response data readStream

    "Modified: / 14-09-2010 / 19:16:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-09-2011 / 12:34:23 / cg"
    "Modified: / 26-08-2018 / 16:15:24 / Claus Gittinger"
!

description
        ^ self location

    "Modified: / 26-08-2018 / 16:15:33 / Claus Gittinger"
!

flushCache
	super flushCache.
	readerCache := nil.
!

readStreamForFileNamed: aString do: aBlock

    | response |
    response := HTTPInterface get: (self urlForFileNamed: aString) userName: self user password: self password.
    ^response responseCode == 200 
        ifTrue: [
            "/ self assertBinaryResponse: client response.
            "immediately cache the version and avoid an unnecessary serialization"
            "/ self cacheRawVersionNamed: aString stream: client contents ].
            aBlock value: response data readStream.
        ].

    "Modified: / 14-09-2010 / 19:38:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 26-08-2018 / 14:17:03 / Claus Gittinger"
!

writeStreamForFileNamed: aString replace: ignoreBoolean do: aBlock
	| stream response |
	stream := RWBinaryOrTextStream on: String new.
	aBlock value: stream.
	response := HTTPSocket
					httpPut: stream contents
					to: (self urlForFileNamed: aString)
					user: self user
					passwd: self password.

	(#( 'HTTP/1.1 201 ' 'HTTP/1.1 200 ' 'HTTP/1.0 201 ' 'HTTP/1.0 200 ')
		anySatisfy: [:code | response beginsWith: code ])
			ifFalse: [self error: response].
! !

!MCHttpRepository methodsFor:'storing'!

storeVersion: aVersion
	self retryOnCredentialRequest: [ super storeVersion: aVersion ]
! !

!MCHttpRepository class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '$Id$'
! !