[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

api[panoramio] code

! Smalltalk bindingsFor: #PanoramioConstants ! ! !

NativeLibraryObject
 subclass: #Panoramio
 instanceVariableNames: ''
 category: 'Panoramio'!
Panoramio comment: '
	Root of Panoramio Objects framework.
	http://www.panoramio.com/api/data/api.html
	@2012 Alejandro Reimondo - [email protected]

	The Panoramio Widget API is free for both commercial and non-commercial purposes that dont exceed the restrictions.
	However, Panoramio reserves the right to charge fees for the use of Panoramio Widget API for some kind of commercial applications and over certain bandwidth limits.
	More information at Panoramio Widget API - Terms of Service.
	http://www.panoramio.com/api/widget/terms.html
'!

! Panoramio class methodsFor: 'code generation' !
classToken
	" Private - Return the classToken to prepend/tag the receiver. "

	^#Panoramio! !

"---------- Custom Code Generation Utilities-----------------"!

! Panoramio class methodsFor: 'code generation' !
wrapFunctions: selectors
	" Private - Generate code to delegate selectors on instance handle. "

	selectors do: [:each| self wrapFunction: each ]! !

! Panoramio class methodsFor: 'code generation' !
wrapFunction: selector
	" Private - Generate code to delegate message on instance handle. "

	| args header code input argStream part |
	input := selector stream.
	args :=  (1 to: (selector occurrencesOf: $:)) collect: [:i| #arg , i asString ].
	args size = 1 ifTrue: [ args := #( #anObject ) ].
	header := '' stream. code := '' stream.
	argStream := args stream.
	code   nextPut: input peek.
	header nextPut: input next asLowercase.
	[ argStream atEnd ] whileFalse: [
		part := (input upTo: $:) ,': ' ,argStream next.
		code   nextPutAll: part ,' handle '.
		header nextPutAll: part ,' '.
	].
	part := input upToEnd.
	code   nextPutAll: part.
	header nextPutAll: part.

	self
		implement: header contents
		  comment: 'Wrap method delegating ',selector,' to handle.'
		  as: '^self handle #',code contents
		  category: #wrappers! !

! Panoramio class methodsFor: 'code generation' !
wrapGetters: selectors
	" Private - Generate code to delegate get selectors on instance handle. "

	selectors do: [:each|
		self wrapFunction: #get
			,each first asUppercase
			,(each copyFrom: 2 to: each size)
	]! !

"---------- Build classes -----------------"!
Panoramio buildSubclasses: #(
	#( #PhotoRequest #( options ) )
	#Widget #Photo #Events
	#PhotoClickedEvent
	#Coordinates
	#( #TermsOfServiceWidget #( element ) )
	#( #TermsOfServiceWidget #( element options ) )
	#PhotoRequestOptions
	#PhotoWidgetOptions
	#PhotoListWidgetOptions
	#TermsOfServiceWidgetOptions
)!
PanoramioWidget buildSubclasses: #(
	#( #PhotoWidget #( element ) )
	#( #PhotoWidget #( element photoRequest ) )
	#( #PhotoWidget #( element photoRequest options ) )
	#( #PhotoListWidget #( element ) )
	#( #PhotoListWidget #( element photoRequest ) )
	#( #PhotoListWidget #( element photoRequest options ) )
)!

"---------- Build accessors -----------------"!
PanoramioPhotoRequestOptions buildAccessors: #(
	group ids order rect set tag user
).!
PanoramioWidget wrapFunctions: #(
	#enableNextArrow: #enablePreviousArrow:
	#getAtEnd #getAtStart
)!
PanoramioPhotoWidget wrapGetters: #(
	photo position
).
PanoramioPhotoWidget wrapFunctions: #(
	#setPosition: #setRequest:
)!
PanoramioPhotoWidgetOptions buildAccessors: #(
	attributionStyle croppedPhotos
	disableDefaultEvents
	width height
).!
PanoramioPhotoListWidget wrapGetters: #(
	photos position
).
PanoramioPhotoListWidget wrapFunctions: #(
	#setPosition: #setRequest:
)!
PanoramioPhotoListWidgetOptions buildAccessors: #(
	attributionStyle croppedPhotos
	disableDefaultEvents
	width height rows columns
	orientation
).!
PanoramioEvents wrapFunctions: #(
	#listen:type:listener:
	#listen:type:listener:capture:
	#listen:type:listener:capture:handler:
	#unlisten:type:listener:
	#unlisten:type:listener:capture:
	#unlisten:type:listener:capture:handler:
	#unlistenByKey:
)!
PanoramioPhotoClickedEvent wrapGetters: #(
	photo position
)!
PanoramioPhoto wrapGetters: #(
	height width position
	ownerId ownerName ownerUrl
	photoId photoTitle photoUrl
)!
PanoramioCoordinates buildAccessors: #(
	lat lng
)!
PanoramioTermsOfServiceWidget wrapGetters: #( height ).!
PanoramioTermsOfServiceWidgetOptions buildAccessors: #(
	width
).!

"------------- Top level implementation -----------------------"!
! Panoramio class methodsFor: 'private' !
loadLibrary
	" Private - Load the library of the receiver. "

	DOM document
		addJavascript: self libraryURL
		onLoad: [
			self loadConstants.
			NativeLibraryObject libraryBound: self name.
		]! !

! Panoramio class methodsFor: 'private' !
libraryURL
	" Private - Return the URL of the library of the receiver. "

	^'http://www.panoramio.com/wapi/wapi.js?v=1'! !

! Panoramio class methodsFor: 'private' !
globalName
	" Private - Return the name of the global to detect/access the library of the receiver. "

	^#panoramio! !

! Panoramio class methodsFor: 'source code' !
sourceCode
	" Private - Return the source code of the Panoramio library.
	We do dynamic binding, and library will be loaded dynamically.
	It is an error situation to try to load the library from sources.
	If this error is triggered can be because the library is still loading or it is no more downloadable from the web.
	"

	self loadLibrary. "we will try to link the binding script."
	^self error: 'This should not happen.'! !

! Panoramio class methodsFor: 'constants' !
poolDictionarySpec
	" Return the mapping of pool dictionary constants. "

	^#(
	#( #StatusCode #( #OK #ERROR 'NETWORK_ERROR' 'NO_REQUEST' ) )
	#( #Cropping #( 'NO_CROPPING' 'TO_SQUARE' 'TO_FILL' ) )
	#( #events #EventType #( 'PHOTO_CHANGED' 'PREVIOUS_CLICKED' 'NEXT_CLICKED' 'PHOTO_CLICKED' 'PHOTO_HTML_CREATED' ) )
	#( #tos #Style #( #HIDDEN #DEFAULT 'HIDDEN_NO_NAME' 'DEFAULT_ADD' ) )
"	----- Broken exports in Panoramio's library -----
	#( #PhotoListWidgetOptions #Orientation #( #HORIZONTAL #VERTICAL ) )
	#( #PhotoSet #( #ALL #PUBLIC #RECENT ) )
	#( #PhotoOrder #( #DATE 'DATE_DESC' ) )
	#( #WidgetTransitionType #( #NONE 'SLIDE_PREVIOUS' 'SLIDE_NEXT' ))
"	)! !

! Panoramio class methodsFor: 'initialize' !
initializeConstants: root
	" Private - Load the constants pool with values from root object. "

	| pool current path |
	pool := Smalltalk at: #PanoramioConstants ifAbsentPut: [ Dictionary new ].
	self poolDictionarySpec do: [:tuple|
		current := root. path := ''.
		tuple do: [:each|
			each isString ifTrue: [
				path := path , each first asUppercase, (each copyFrom: 2 to: each size).
				current notNil ifTrue: [ current := current basicAt: each ].
			] ifFalse: [ each do: [:key|
				pool
					at: path ,(key asLowercase asSmalltalkName: true)
					put: (current notNil ifTrue: [ current[key] ] ifFalse: [ key ])
			] ]
		].
	].! !

! Panoramio class methodsFor: 'initialize' !
loadConstants
	" Private - Initialize constants from library. "

	^self initializeConstants: self library! !

! Panoramio class methodsFor: 'initialize' !
initializeConstants
	" Private - Initialize constants with defaults. "

	^self initializeConstants: nil! !

! Panoramio class methodsFor: 'private' !
poolVariableNamed: spec
	" Private - Return name of pool variable global from spec. "

	| upper | upper := true.
	^spec inject: String new into: [:total :c|
		c = $_ ifTrue: [ upper := true. total ]
		ifFalse: [ upper
			ifTrue: [ upper := false. total, c asUppercase ]
			ifFalse: [ total , c asLowercase ]
		]
	]! !

"------------- Custom implementation -----------------------"!
Panoramio initializeConstants.

! Panoramio class methodsFor: 'accessing' !
events
	" Return a wrapper to panoramio.events "

	^PanoramioEvent @ (self global: #events)! !

! Panoramio class methodsFor: 'accessing' !
tos
	" Return a wrapper to panoramio.tos (TermsOfService) "

	^PanoramioEvent @ (self global: #tos)! !